/usr/lib/ocaml/gsl/gsl_multiroot.mli is in libocamlgsl-ocaml-dev 1.19.1-1.
This file is owned by root:root, with mode 0o644.
The actual contents of the file can be viewed below.
1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 | (* gsl-ocaml - OCaml interface to GSL *)
(* Copyright (©) 2002-2012 - Olivier Andrieu *)
(* Distributed under the terms of the GPL version 3 *)
(** Multidimensional Root-Finding *)
open Gsl_fun
open Gsl_vector
module NoDeriv :
sig
type kind =
| HYBRIDS
| HYBRID
| DNEWTON
| BROYDEN
type t
val make : kind -> int -> multi_fun -> vector -> t
external name : t -> string
= "ml_gsl_multiroot_fsolver_name"
external iterate : t -> unit
= "ml_gsl_multiroot_fsolver_iterate"
external root : t -> vector -> unit
= "ml_gsl_multiroot_fsolver_root"
external get_state : t ->
?x:vector -> ?f:vector ->
?dx:vector -> unit -> unit
= "ml_gsl_multiroot_fsolver_get_state"
external test_delta : t -> epsabs:float -> epsrel:float -> bool
= "ml_gsl_multiroot_test_delta_f"
external test_residual : t -> epsabs:float -> bool
= "ml_gsl_multiroot_test_residual_f"
end
module Deriv :
sig
type kind =
| HYBRIDSJ
| HYBRIDJ
| NEWTON
| GNEWTON
type t
val make : kind -> int -> multi_fun_fdf -> vector -> t
external name : t -> string
= "ml_gsl_multiroot_fdfsolver_name"
external iterate : t -> unit
= "ml_gsl_multiroot_fdfsolver_iterate"
external root : t -> vector -> unit
= "ml_gsl_multiroot_fdfsolver_root"
external get_state : t ->
?x:vector -> ?f:vector ->
?j:Gsl_matrix.matrix -> ?dx:vector -> unit -> unit
= "ml_gsl_multiroot_fdfsolver_get_state_bc" "ml_gsl_multiroot_fdfsolver_get_state"
external test_delta : t -> epsabs:float -> epsrel:float -> bool
= "ml_gsl_multiroot_test_delta_fdf"
external test_residual : t -> epsabs:float -> bool
= "ml_gsl_multiroot_test_residual_fdf"
end
|