1 (***********************************************************************)
5 (* Jacques Garrigue, Kyoto University RIMS *)
7 (* Copyright 2001 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the GNU Library General Public License, with *)
10 (* the special exception on linking described in file ../LICENSE. *)
12 (***********************************************************************)
16 (** Extra labeled libraries.
18 This meta-module provides labelized version of the {!Hashtbl},
19 {!Map} and {!Set} modules.
21 They only differ by their labels. They are provided to help
22 porting from previous versions of Objective Caml.
23 The contents of this module are subject to change.
27 type ('a
, 'b
) t
= ('a
, 'b
) Hashtbl.t
28 val create
: int -> ('a
, 'b
) t
29 val clear
: ('a
, 'b
) t
-> unit
30 val add
: ('a
, 'b
) t
-> key
:'a
-> data
:'b
-> unit
31 val copy
: ('a
, 'b
) t
-> ('a
, 'b
) t
32 val find
: ('a
, 'b
) t
-> 'a
-> 'b
33 val find_all
: ('a
, 'b
) t
-> 'a
-> 'b list
34 val mem
: ('a
, 'b
) t
-> 'a
-> bool
35 val remove
: ('a
, 'b
) t
-> 'a
-> unit
36 val replace
: ('a
, 'b
) t
-> key
:'a
-> data
:'b
-> unit
37 val iter
: f
:(key
:'a
-> data
:'b
-> unit) -> ('a
, 'b
) t
-> unit
39 f
:(key
:'a
-> data
:'b
-> 'c
-> 'c
) ->
40 ('a
, 'b
) t
-> init
:'c
-> 'c
41 val length
: ('a
, 'b
) t
-> int
42 module type HashedType
= Hashtbl.HashedType
47 val create
: int -> 'a t
48 val clear
: 'a t
-> unit
49 val copy
: 'a t
-> 'a t
50 val add
: 'a t
-> key
:key
-> data
:'a
-> unit
51 val remove
: 'a t
-> key
-> unit
52 val find
: 'a t
-> key
-> 'a
53 val find_all
: 'a t
-> key
-> 'a list
54 val replace
: 'a t
-> key
:key
-> data
:'a
-> unit
55 val mem
: 'a t
-> key
-> bool
56 val iter
: f
:(key
:key
-> data
:'a
-> unit) -> 'a t
-> unit
58 f
:(key
:key
-> data
:'a
-> 'b
-> 'b
) ->
60 val length
: 'a t
-> int
62 module Make
: functor (H
: HashedType
) -> S
with type key
= H.t
64 external hash_param
: int -> int -> 'a
-> int
65 = "caml_hash_univ_param" "noalloc"
69 module type OrderedType
= Map.OrderedType
75 val is_empty
: 'a t
-> bool
76 val add
: key
:key
-> data
:'a
-> 'a t
-> 'a t
77 val find
: key
-> 'a t
-> 'a
78 val remove
: key
-> 'a t
-> 'a t
79 val mem
: key
-> 'a t
-> bool
80 val iter
: f
:(key
:key
-> data
:'a
-> unit) -> 'a t
-> unit
81 val map
: f
:('a
-> 'b
) -> 'a t
-> 'b t
82 val mapi
: f
:(key
-> 'a
-> 'b
) -> 'a t
-> 'b t
84 f
:(key
:key
-> data
:'a
-> 'b
-> 'b
) ->
86 val compare
: cmp
:('a
-> 'a
-> int) -> 'a t
-> 'a t
-> int
87 val equal
: cmp
:('a
-> 'a
-> bool) -> 'a t
-> 'a t
-> bool
89 module Make
: functor (Ord
: OrderedType
) -> S
with type key
= Ord.t
93 module type OrderedType
= Set.OrderedType
99 val is_empty
: t
-> bool
100 val mem
: elt
-> t
-> bool
101 val add
: elt
-> t
-> t
102 val singleton
: elt
-> t
103 val remove
: elt
-> t
-> t
104 val union
: t
-> t
-> t
105 val inter
: t
-> t
-> t
106 val diff
: t
-> t
-> t
107 val compare
: t
-> t
-> int
108 val equal
: t
-> t
-> bool
109 val subset
: t
-> t
-> bool
110 val iter
: f
:(elt
-> unit) -> t
-> unit
111 val fold
: f
:(elt
-> 'a
-> 'a
) -> t
-> init
:'a
-> 'a
112 val for_all
: f
:(elt
-> bool) -> t
-> bool
113 val exists
: f
:(elt
-> bool) -> t
-> bool
114 val filter
: f
:(elt
-> bool) -> t
-> t
115 val partition
: f
:(elt
-> bool) -> t
-> t
* t
116 val cardinal
: t
-> int
117 val elements
: t
-> elt list
118 val min_elt
: t
-> elt
119 val max_elt
: t
-> elt
120 val choose
: t
-> elt
121 val split
: elt
-> t
-> t
* bool * t
123 module Make
: functor (Ord
: OrderedType
) -> S
with type elt
= Ord.t