Skip to content

Commit

Permalink
Use Lib_name.t instead of string
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <[email protected]>
  • Loading branch information
nojb committed Jun 25, 2020
1 parent 5229892 commit 550f445
Show file tree
Hide file tree
Showing 7 changed files with 11 additions and 10 deletions.
2 changes: 2 additions & 0 deletions bin/arg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -122,3 +122,5 @@ let bytes =
conv (decode, pp_print_int64)

let context_name : Context_name.t conv = conv Context_name.conv

let lib_name = conv Dune.Lib_name.conv
2 changes: 2 additions & 0 deletions bin/arg.mli
Original file line number Diff line number Diff line change
Expand Up @@ -36,3 +36,5 @@ val path : Path.t conv
val package_name : Package.Name.t conv

val profile : Profile.t conv

val lib_name : Lib_name.t conv
4 changes: 2 additions & 2 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ type t =
; stats_trace_file : string option
; always_show_command_line : bool
; promote_install_files : bool
; instrument_with : string list option
; instrument_with : Dune.Lib_name.t list option
}

let workspace_file t = t.workspace_file
Expand Down Expand Up @@ -638,7 +638,7 @@ let term =
in
Arg.(
value
& opt (some (list string)) None
& opt (some (list lib_name)) None
& info [ "instrument-with" ] ~docs
~env:(Arg.env_var ~doc "DUNE_INSTRUMENT_WITH")
~docv:"BACKENDS" ~doc)
Expand Down
2 changes: 1 addition & 1 deletion bin/common.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ val default_target : t -> Arg.Dep.t

val prefix_target : t -> string -> string

val instrument_with : t -> string list option
val instrument_with : t -> Dune.Lib_name.t list option

(** [set_common ?log common ~targets ~external_lib_deps_mode] is
[set_dirs common] followed by [set_common_other common ~targets]. In
Expand Down
2 changes: 1 addition & 1 deletion src/dune/main.mli
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ val scan_workspace :
-> ?x:Context_name.t
-> ?capture_outputs:bool
-> ?profile:Profile.t
-> ?instrument_with:string list
-> ?instrument_with:Lib_name.t list
-> ancestor_vcs:Vcs.t option
-> unit
-> workspace Fiber.t
Expand Down
7 changes: 2 additions & 5 deletions src/dune/workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -470,7 +470,7 @@ module DB = struct
type t =
{ x : Context_name.t option
; profile : Profile.t option
; instrument_with : string list option
; instrument_with : Lib_name.t list option
; path : Path.t option
}

Expand All @@ -479,7 +479,7 @@ module DB = struct
record
[ ("x", option Context_name.to_dyn x)
; ("profile", option Profile.to_dyn profile)
; ("instrument_with", option (list string) instrument_with)
; ("instrument_with", option (list Lib_name.to_dyn) instrument_with)
; ("path", option Path.to_dyn path)
]

Expand All @@ -497,9 +497,6 @@ let workspace =
let { DB.Settings.path; profile; instrument_with; x } =
Memo.Run.Fdecl.get DB.Settings.t
in
let instrument_with =
Option.map ~f:(List.map ~f:Lib_name.of_string) instrument_with
in
match path with
| None -> default ?x ?profile ?instrument_with ()
| Some p -> load ?x ?profile ?instrument_with p
Expand Down
2 changes: 1 addition & 1 deletion src/dune/workspace.mli
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ val hash : t -> int
val init :
?x:Context_name.t
-> ?profile:Profile.t
-> ?instrument_with:string list
-> ?instrument_with:Lib_name.t list
-> ?path:Path.t
-> unit
-> unit
Expand Down

0 comments on commit 550f445

Please sign in to comment.