Skip to content

Commit 385a3eb

Browse files
authored
Merge pull request #1081 from rgrinberg/remove-string-map
Remove String_map module
2 parents d6c2a43 + 6e29bd1 commit 385a3eb

File tree

10 files changed

+22
-21
lines changed

10 files changed

+22
-21
lines changed

bin/main.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1436,11 +1436,11 @@ let printenv =
14361436
match Path.extract_build_context dir with
14371437
| Some (ctx, _) ->
14381438
let sctx =
1439-
String_map.find setup.scontexts ctx |> Option.value_exn
1439+
String.Map.find setup.scontexts ctx |> Option.value_exn
14401440
in
14411441
[dump sctx ~dir]
14421442
| None ->
1443-
String_map.values setup.scontexts
1443+
String.Map.values setup.scontexts
14441444
|> List.map ~f:(fun sctx ->
14451445
let dir =
14461446
Path.append (Super_context.context sctx).build_dir dir

src/gen_rules.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -794,6 +794,6 @@ let gen ~contexts ~build_system
794794
Fiber.parallel_map contexts ~f:make_sctx >>| fun l ->
795795
let map = String.Map.of_list_exn l in
796796
Build_system.set_rule_generators build_system
797-
(String_map.map map ~f:(fun (module M : Gen) -> M.gen_rules));
798-
String_map.iter map ~f:(fun (module M : Gen) -> M.init ());
799-
String_map.map map ~f:(fun (module M : Gen) -> M.sctx)
797+
(String.Map.map map ~f:(fun (module M : Gen) -> M.gen_rules));
798+
String.Map.iter map ~f:(fun (module M : Gen) -> M.init ());
799+
String.Map.map map ~f:(fun (module M : Gen) -> M.sctx)

src/gen_rules.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,4 +7,4 @@ val gen
77
-> ?external_lib_deps_mode:bool (* default: false *)
88
-> ?only_packages:Package.Name.Set.t
99
-> Jbuild_load.conf
10-
-> Super_context.t String_map.t Fiber.t
10+
-> Super_context.t String.Map.t Fiber.t

src/import.ml

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -9,15 +9,6 @@ let ksprintf = Printf.ksprintf
99

1010
let initial_cwd = Sys.getcwd ()
1111

12-
module String_map = struct
13-
include String.Map
14-
15-
let pp f fmt t =
16-
Format.pp_print_list (fun fmt (k, v) ->
17-
Format.fprintf fmt "@[<hov 2>(%s@ =@ %a)@]" k f v
18-
) fmt (to_list t)
19-
end
20-
2112
module Sys = struct
2213
include Sys
2314

src/main.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ let () = Inline_tests.linkme
66
type setup =
77
{ build_system : Build_system.t
88
; contexts : Context.t list
9-
; scontexts : Super_context.t String_map.t
9+
; scontexts : Super_context.t String.Map.t
1010
; packages : Package.t Package.Name.Map.t
1111
; file_tree : File_tree.t
1212
; env : Env.t

src/main.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ open! Import
33
type setup =
44
{ build_system : Build_system.t
55
; contexts : Context.t list
6-
; scontexts : Super_context.t String_map.t
6+
; scontexts : Super_context.t String.Map.t
77
; packages : Package.t Package.Name.Map.t
88
; file_tree : File_tree.t
99
; env : Env.t

src/meta.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -141,7 +141,7 @@ module Simplified = struct
141141
let rec pp fmt t =
142142
Fmt.record fmt
143143
[ "name", Fmt.const Fmt.quoted t.name
144-
; "vars", Fmt.const (String_map.pp Rules.pp) t.vars
144+
; "vars", Fmt.const (String.Map.pp Rules.pp) t.vars
145145
; "subs", Fmt.const (Fmt.ocaml_list pp) t.subs
146146
]
147147
end

src/stdune/string.ml

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -202,7 +202,13 @@ let maybe_quoted s =
202202
Printf.sprintf {|"%s"|} escaped
203203

204204
module Set = Set.Make(T)
205-
module Map = Map.Make(T)
205+
module Map = struct
206+
include Map.Make(T)
207+
let pp f fmt t =
208+
Format.pp_print_list (fun fmt (k, v) ->
209+
Format.fprintf fmt "@[<hov 2>(%s@ =@ %a)@]" k f v
210+
) fmt (to_list t)
211+
end
206212
module Table = Hashtbl.Make(T)
207213

208214
let enumerate_gen s =

src/stdune/string.mli

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,5 +52,9 @@ val enumerate_and : string list -> string
5252
val enumerate_or : string list -> string
5353

5454
module Set : Set.S with type elt = t
55-
module Map : Map.S with type key = t
55+
module Map : sig
56+
include Map.S with type key = t
57+
58+
val pp : (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a t -> unit
59+
end
5660
module Table : Hashtbl.S with type key = t

test/unit-tests/tests.mlt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ let print_pkg ppf pkg =
1515
;;
1616

1717
#install_printer print_pkg;;
18-
#install_printer String_map.pp;;
18+
#install_printer String.Map.pp;;
1919

2020
[%%expect{|
2121
val print_pkg : Format.formatter -> Findlib.Package.t -> unit = <fun>

0 commit comments

Comments
 (0)