offer two different functions for combining Map and Seq. Both build

an extended version of Map, with additional conversion functions relative to Sequence.
One can Adapt an already existing Map module, or Make an extended Map directly
This commit is contained in:
Simon Cruanes 2013-02-07 16:07:16 +01:00
parent d706038ed5
commit 07cc9df645
3 changed files with 61 additions and 28 deletions

View file

@ -228,25 +228,39 @@ let to_set (type s) (type v) m seq =
(fun set x -> S.add x set) (fun set x -> S.add x set)
S.empty seq S.empty seq
(** Iterate on maps. The functor must be instantiated with a map type *) (** Conversion between maps and sequences. *)
module Map(M : Map.S) = module Map = struct
struct module type S = sig
type 'a map = 'a M.t type +'a map
type key = M.key include Map.S with type 'a t := 'a map
val to_seq : 'a map -> (key * 'a) t
let to_seq m = val of_seq : (key * 'a) t -> 'a map
from_iter (fun k -> M.iter (fun key value -> k (key, value)) m) val keys : 'a map -> key t
val values : 'a map -> 'a t
let keys m =
from_iter (fun k -> M.iter (fun key _ -> k key) m)
let values m =
from_iter (fun k -> M.iter (fun _ value -> k value) m)
let of_seq seq =
fold (fun m (key,value) -> M.add key value m) M.empty seq
end end
(** Adapt a pre-existing Map module to make it sequence-aware *)
module Adapt(M : Map.S) : S with type key = M.key and type 'a map = 'a M.t = struct
type 'a map = 'a M.t
let to_seq m = from_iter (fun k -> M.iter (fun x y -> k (x,y)) m)
let of_seq seq = fold (fun m (k,v) -> M.add k v m) M.empty seq
let keys m = from_iter (fun k -> M.iter (fun x _ -> k x) m)
let values m = from_iter (fun k -> M.iter (fun _ y -> k y) m)
include M
end
(** Create an enriched Map module, with sequence-aware functions *)
module Make(V : Map.OrderedType) : S with type key = V.t = struct
module M = Map.Make(V)
include Adapt(M)
end
end
(** {2 Pretty printing of sequences} *) (** {2 Pretty printing of sequences} *)
(** Pretty print a sequence of ['a], using the given pretty printer (** Pretty print a sequence of ['a], using the given pretty printer

View file

@ -151,21 +151,24 @@ val of_set : (module Set.S with type elt = 'a and type t = 'b) -> 'b -> 'a t
val to_set : (module Set.S with type elt = 'a and type t = 'b) -> 'a t -> 'b val to_set : (module Set.S with type elt = 'a and type t = 'b) -> 'a t -> 'b
(** Convert the sequence to a set, given the proper set module *) (** Convert the sequence to a set, given the proper set module *)
(** Iterate on maps. The functor must be instantiated with a map type *) (** Conversion between maps and sequences. *)
module Map(M : Map.S) : module Map : sig
sig module type S = sig
type 'a map = 'a M.t type +'a map
type key = M.key include Map.S with type 'a t := 'a map
val to_seq : 'a map -> (key * 'a) t val to_seq : 'a map -> (key * 'a) t
val keys : 'a map -> key t
val values : 'a map -> 'a t
val of_seq : (key * 'a) t -> 'a map val of_seq : (key * 'a) t -> 'a map
val keys : 'a map -> key t
val values : 'a map -> 'a t
end end
(** Adapt a pre-existing Map module to make it sequence-aware *)
module Adapt(M : Map.S) : S with type key = M.key and type 'a map = 'a M.t
(** Create an enriched Map module, with sequence-aware functions *)
module Make(V : Map.OrderedType) : S with type key = V.t
end
(** {2 Pretty printing of sequences} *) (** {2 Pretty printing of sequences} *)
val pp_seq : ?sep:string -> (Format.formatter -> 'a -> unit) -> val pp_seq : ?sep:string -> (Format.formatter -> 'a -> unit) ->

View file

@ -9,9 +9,15 @@ let pp_list ?(sep=", ") pp_item formatter l =
module ISet = Set.Make(struct type t = int let compare = compare end) module ISet = Set.Make(struct type t = int let compare = compare end)
let iset = (module ISet : Set.S with type elt = int and type t = ISet.t) let iset = (module ISet : Set.S with type elt = int and type t = ISet.t)
module OrderedString = struct type t = string let compare = compare end
module SMap = Sequence.Map.Make(OrderedString)
let my_map = SMap.of_seq (Sequence.of_list ["1", 1; "2", 2; "3", 3; "answer", 42])
let sexpr = "(foo bar (bazz quux hello 42) world (zoo foo bar (1 2 (3 4))))" let sexpr = "(foo bar (bazz quux hello 42) world (zoo foo bar (1 2 (3 4))))"
let _ = let _ =
(* lists *)
let l = [0;1;2;3;4;5;6] in let l = [0;1;2;3;4;5;6] in
let l' = Sequence.to_list let l' = Sequence.to_list
(Sequence.filter (fun x -> x mod 2 = 0) (Sequence.of_list l)) in (Sequence.filter (fun x -> x mod 2 = 0) (Sequence.of_list l)) in
@ -39,11 +45,21 @@ let _ =
(Sequence.of_array (Sequence.of_array
(Sequence.to_array (Sequence.append (Sequence.to_array (Sequence.append
(Sequence.take 5 (Sequence.of_list l3)) (Sequence.of_list l4)))); (Sequence.take 5 (Sequence.of_list l3)) (Sequence.of_list l4))));
(* maps *)
Format.printf "@[<h>map: %a@]@."
(Sequence.pp_seq (fun formatter (k,v) -> Format.fprintf formatter "\"%s\" -> %d" k v))
(SMap.to_seq my_map);
let module MyMapSeq = Sequence.Map.Adapt(Map.Make(OrderedString)) in
let my_map' = MyMapSeq.of_seq (Sequence.of_list ["1", 1; "2", 2; "3", 3; "answer", 42]) in
Format.printf "@[<h>map: %a@]@."
(Sequence.pp_seq (fun formatter (k,v) -> Format.fprintf formatter "\"%s\" -> %d" k v))
(MyMapSeq.to_seq my_map');
(* sum *) (* sum *)
let n = 100000000 in let n = 100000000 in
let sum = Sequence.fold (+) 0 (Sequence.take n (Sequence.repeat 1)) in let sum = Sequence.fold (+) 0 (Sequence.take n (Sequence.repeat 1)) in
Format.printf "%dx1 = %d@." n sum; Format.printf "%dx1 = %d@." n sum;
assert (n=sum); assert (n=sum);
(* sexpr *)
let s = Sexpr.of_seq (Sexpr.lex (Sequence.of_str sexpr)) in let s = Sexpr.of_seq (Sexpr.lex (Sequence.of_str sexpr)) in
let s = Sexpr.of_seq (Sequence.map let s = Sexpr.of_seq (Sequence.map
(function | `Atom s -> `Atom (String.capitalize s) | tok -> tok) (function | `Atom s -> `Atom (String.capitalize s) | tok -> tok)