Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1436,11 +1436,11 @@ let printenv =
match Path.extract_build_context dir with
| Some (ctx, _) ->
let sctx =
String_map.find setup.scontexts ctx |> Option.value_exn
String.Map.find setup.scontexts ctx |> Option.value_exn
in
[dump sctx ~dir]
| None ->
String_map.values setup.scontexts
String.Map.values setup.scontexts
|> List.map ~f:(fun sctx ->
let dir =
Path.append (Super_context.context sctx).build_dir dir
Expand Down
6 changes: 3 additions & 3 deletions src/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -794,6 +794,6 @@ let gen ~contexts ~build_system
Fiber.parallel_map contexts ~f:make_sctx >>| fun l ->
let map = String.Map.of_list_exn l in
Build_system.set_rule_generators build_system
(String_map.map map ~f:(fun (module M : Gen) -> M.gen_rules));
String_map.iter map ~f:(fun (module M : Gen) -> M.init ());
String_map.map map ~f:(fun (module M : Gen) -> M.sctx)
(String.Map.map map ~f:(fun (module M : Gen) -> M.gen_rules));
String.Map.iter map ~f:(fun (module M : Gen) -> M.init ());
String.Map.map map ~f:(fun (module M : Gen) -> M.sctx)
2 changes: 1 addition & 1 deletion src/gen_rules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -7,4 +7,4 @@ val gen
-> ?external_lib_deps_mode:bool (* default: false *)
-> ?only_packages:Package.Name.Set.t
-> Jbuild_load.conf
-> Super_context.t String_map.t Fiber.t
-> Super_context.t String.Map.t Fiber.t
9 changes: 0 additions & 9 deletions src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,15 +9,6 @@ let ksprintf = Printf.ksprintf

let initial_cwd = Sys.getcwd ()

module String_map = struct
include String.Map

let pp f fmt t =
Format.pp_print_list (fun fmt (k, v) ->
Format.fprintf fmt "@[<hov 2>(%s@ =@ %a)@]" k f v
) fmt (to_list t)
end

module Sys = struct
include Sys

Expand Down
2 changes: 1 addition & 1 deletion src/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ let () = Inline_tests.linkme
type setup =
{ build_system : Build_system.t
; contexts : Context.t list
; scontexts : Super_context.t String_map.t
; scontexts : Super_context.t String.Map.t
; packages : Package.t Package.Name.Map.t
; file_tree : File_tree.t
; env : Env.t
Expand Down
2 changes: 1 addition & 1 deletion src/main.mli
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ open! Import
type setup =
{ build_system : Build_system.t
; contexts : Context.t list
; scontexts : Super_context.t String_map.t
; scontexts : Super_context.t String.Map.t
; packages : Package.t Package.Name.Map.t
; file_tree : File_tree.t
; env : Env.t
Expand Down
2 changes: 1 addition & 1 deletion src/meta.ml
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,7 @@ module Simplified = struct
let rec pp fmt t =
Fmt.record fmt
[ "name", Fmt.const Fmt.quoted t.name
; "vars", Fmt.const (String_map.pp Rules.pp) t.vars
; "vars", Fmt.const (String.Map.pp Rules.pp) t.vars
; "subs", Fmt.const (Fmt.ocaml_list pp) t.subs
]
end
Expand Down
8 changes: 7 additions & 1 deletion src/stdune/string.ml
Original file line number Diff line number Diff line change
Expand Up @@ -202,7 +202,13 @@ let maybe_quoted s =
Printf.sprintf {|"%s"|} escaped

module Set = Set.Make(T)
module Map = Map.Make(T)
module Map = struct
include Map.Make(T)
let pp f fmt t =
Format.pp_print_list (fun fmt (k, v) ->
Format.fprintf fmt "@[<hov 2>(%s@ =@ %a)@]" k f v
) fmt (to_list t)
end
module Table = Hashtbl.Make(T)

let enumerate_gen s =
Expand Down
6 changes: 5 additions & 1 deletion src/stdune/string.mli
Original file line number Diff line number Diff line change
Expand Up @@ -52,5 +52,9 @@ val enumerate_and : string list -> string
val enumerate_or : string list -> string

module Set : Set.S with type elt = t
module Map : Map.S with type key = t
module Map : sig
include Map.S with type key = t

val pp : (Format.formatter -> 'a -> unit) -> Format.formatter -> 'a t -> unit
end
module Table : Hashtbl.S with type key = t
2 changes: 1 addition & 1 deletion test/unit-tests/tests.mlt
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ let print_pkg ppf pkg =
;;

#install_printer print_pkg;;
#install_printer String_map.pp;;
#install_printer String.Map.pp;;

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