/usr/lib/ocaml/deriving/utils.mli is in libderiving-ocsigen-ocaml-dev 0.7.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 | (* Copyright Jeremy Yallop 2007.
Copyright Grégoire Henry 2011.
This file is free software, distributed under the MIT license.
See the file COPYING for details.
*)
type ('a, 'b) either = Left of 'a | Right of 'b
val either_partition :
('a -> ('b, 'c) either) -> 'a list -> 'b list * 'c list
module List : sig
include module type of List
val fold_left1 : ('a -> 'a -> 'a) -> 'a list -> 'a
val fold_right1 : ('a -> 'a -> 'a) -> 'a list -> 'a
val range : int -> int -> int list
val last : 'a list -> 'a
val concat_map : ('a -> 'b list) -> 'a list -> 'b list
val concat_map2 : ('a -> 'b -> 'c list) -> 'a list -> 'b list -> 'c list
val mapn : ?init:int -> ('a -> int -> 'b) -> 'a list -> 'b list
val zip : 'a list -> 'b list -> ('a * 'b) list
val split3 : ('a * 'b * 'c) list -> 'a list * 'b list * 'c list
end
module F : sig
val id : 'a -> 'a
val curry : ('a * 'b -> 'c) -> 'a -> 'b -> 'c
val uncurry : ('a -> 'b -> 'c) -> 'a * 'b -> 'c
end
module Option : sig
val map : ('a -> 'b) -> 'a option -> 'b option
end
module DumpAst : sig
val ident : Camlp4.PreCast.Ast.ident -> string
val ctyp : Camlp4.PreCast.Ast.ctyp -> string
end
module Map : sig
module type OrderedType = Map.OrderedType
module type S = sig
include Map.S
exception Not_found of key
val fromList : (key * 'a) list -> 'a t
val union_disjoint : 'a t list -> 'a t
val union_disjoint2 : 'a t -> 'a t -> 'a t
end
module Make (Ord : OrderedType) : S with type key = Ord.t
end
module Set : sig
module type OrderedType = Set.OrderedType
module type S = sig
include Set.S
val toList : t -> elt list
val fromList : elt list -> t
end
module Make (Ord : OrderedType) : S with type elt = Ord.t
end
val random_id : int -> string
val tag_hash : string -> int
val typevar_of_int : int -> string
|