1(*
2 * Copyright (C) 2008-2009 Citrix Ltd.
3 * Author Thomas Gazagnaire <thomas.gazagnaire@eu.citrix.com>
4 *
5 * This program is free software; you can redistribute it and/or modify
6 * it under the terms of the GNU Lesser General Public License as published
7 * by the Free Software Foundation; version 2.1 only. with the special
8 * exception on linking described in file LICENSE.
9 *
10 * This program is distributed in the hope that it will be useful,
11 * but WITHOUT ANY WARRANTY; without even the implied warranty of
12 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
13 * GNU Lesser General Public License for more details.
14 *)
15
16(** Basic Implementation of polymorphic tries (ie. prefix trees) *)
17
18type ('a, 'b) t
19(** The type of tries. ['a list] is the type of keys, ['b] the type of values.
20	Internally, a trie is represented as a labeled tree, where node contains values
21	of type ['a * 'b option]. *)
22
23val create : unit -> ('a,'b) t
24(** Creates an empty trie. *)
25
26val mem : ('a,'b) t -> 'a list -> bool
27(** [mem t k] returns true if a value is associated with the key [k] in the trie [t].
28	Otherwise, it returns false. *)
29
30val find : ('a, 'b) t -> 'a list -> 'b
31(** [find t k] returns the value associated with the key [k] in the trie [t].
32	Returns [Not_found] if no values are associated with [k] in [t]. *)
33
34val set : ('a, 'b) t -> 'a list -> 'b -> ('a, 'b) t
35(** [set t k v] associates the value [v] with the key [k] in the trie [t]. *)
36
37val unset : ('a, 'b) t -> 'a list -> ('a, 'b) t
38(** [unset k v] removes the association of value [v] with the key [k] in the trie [t].
39	Moreover, it automatically clean the trie, ie. it removes recursively
40	every nodes of [t] containing no values and having no chil. *)
41
42val iter : ('a -> 'b option -> unit) -> ('a, 'b) t -> unit
43(** [iter f t] applies the function [f] to every node of the trie [t].
44	As nodes of the trie [t] do not necessary contains a value, the second argument of
45	[f] is an option type. *)
46
47val iter_path : ('a -> 'b option -> unit) -> ('a, 'b) t -> 'a list -> unit
48(** [iter_path f t p] iterates [f] over nodes associated with the path [p] in the trie [t].
49	If [p] is not a valid path of [t], it iterates on the longest valid prefix of [p]. *)
50
51val fold : ('a -> 'b option -> 'c -> 'c) -> ('a, 'b) t -> 'c -> 'c
52(** [fold f t x] fold [f] over every nodes of [t], with [x] as initial value. *)
53
54val map : ('b -> 'c option) -> ('a,'b) t -> ('a,'c) t
55(** [map f t] maps [f] over every values stored in [t]. The return value of [f] is of type 'c option
56	as one may wants to remove value associated to a key. This function is not tail-recursive. *)
57
58val sub : ('a, 'b) t -> 'a list -> ('a,'b) t
59(** [sub t p] returns the sub-trie associated with the path [p] in the trie [t].
60	If [p] is not a valid path of [t], it returns an empty trie. *)
61