Skip to content

Commit 7a37df2

Browse files
committed
[coq] remove Config module
Signed-off-by: Enrico Tassi <[email protected]>
1 parent 2b6f519 commit 7a37df2

File tree

4 files changed

+70
-76
lines changed

4 files changed

+70
-76
lines changed

src/dune_rules/coq/coq_config.ml

Lines changed: 49 additions & 53 deletions
Original file line numberDiff line numberDiff line change
@@ -195,61 +195,58 @@ module Version = struct
195195
;;
196196
end
197197

198-
module Config = struct
199-
type t =
200-
{ coqlib : Path.t
201-
; coqcorelib : Path.t option (* this is not available in Coq < 8.14 *)
202-
; coq_native_compiler_default :
203-
string option (* this is not available in Coq < 8.13 *)
204-
}
198+
type t =
199+
{ coqlib : Path.t
200+
; coqcorelib : Path.t option (* this is not available in Coq < 8.14 *)
201+
; coq_native_compiler_default : string option (* this is not available in Coq < 8.13 *)
202+
}
205203

206-
let impl_config bin =
207-
let* _ = Build_system.build_file bin in
208-
Memo.of_reproducible_fiber
209-
@@ Process.run_capture_lines
210-
~display:Quiet
211-
~stderr_to:
212-
(Process.Io.make_stderr
213-
~output_on_success:Swallow
214-
~output_limit:Execution_parameters.Action_output_limit.default)
215-
Return
216-
bin
217-
[ "--config" ]
218-
;;
204+
let impl_config bin =
205+
let* _ = Build_system.build_file bin in
206+
Memo.of_reproducible_fiber
207+
@@ Process.run_capture_lines
208+
~display:Quiet
209+
~stderr_to:
210+
(Process.Io.make_stderr
211+
~output_on_success:Swallow
212+
~output_limit:Execution_parameters.Action_output_limit.default)
213+
Return
214+
bin
215+
[ "--config" ]
216+
;;
219217

220-
let config_memo = Memo.create "coq-config" ~input:(module Path) impl_config
218+
let config_memo = Memo.create "coq-config" ~input:(module Path) impl_config
221219

222-
let make ~(coqc : Action.Prog.t) =
223-
let open Memo.O in
224-
let+ config_output =
225-
get_output_from_config_or_version ~coqc ~what:"--config" config_memo
226-
in
227-
let open Result.O in
228-
let* config_output = config_output in
229-
match Vars.of_lines config_output with
230-
| Ok vars ->
231-
let coqlib = Vars.get_path vars "COQLIB" in
232-
(* this is not available in Coq < 8.14 *)
233-
let coqcorelib = Vars.get_path_opt vars "COQCORELIB" in
234-
(* this is not available in Coq < 8.13 *)
235-
let coq_native_compiler_default = Vars.get_opt vars "COQ_NATIVE_COMPILER_DEFAULT" in
236-
Ok { coqlib; coqcorelib; coq_native_compiler_default }
237-
| Error msg ->
238-
User_error.raise Pp.[ textf "Cannot parse output of coqc --config:"; msg ]
239-
;;
220+
let make ~(coqc : Action.Prog.t) =
221+
let open Memo.O in
222+
let+ config_output =
223+
get_output_from_config_or_version ~coqc ~what:"--config" config_memo
224+
in
225+
let open Result.O in
226+
let* config_output = config_output in
227+
match Vars.of_lines config_output with
228+
| Ok vars ->
229+
let coqlib = Vars.get_path vars "COQLIB" in
230+
(* this is not available in Coq < 8.14 *)
231+
let coqcorelib = Vars.get_path_opt vars "COQCORELIB" in
232+
(* this is not available in Coq < 8.13 *)
233+
let coq_native_compiler_default = Vars.get_opt vars "COQ_NATIVE_COMPILER_DEFAULT" in
234+
Ok { coqlib; coqcorelib; coq_native_compiler_default }
235+
| Error msg ->
236+
User_error.raise Pp.[ textf "Cannot parse output of coqc --config:"; msg ]
237+
;;
240238

241-
let by_name { coqlib; coqcorelib; coq_native_compiler_default } name =
242-
match name with
243-
| "coqlib" -> Some (Value.path coqlib)
244-
| "coqcorelib" -> Option.map ~f:Value.path coqcorelib
245-
| "coq_native_compiler_default" ->
246-
Option.map ~f:Value.string coq_native_compiler_default
247-
| _ ->
248-
Code_error.raise
249-
"Unknown name was requested from coq_config"
250-
[ "name", Dyn.string name ]
251-
;;
252-
end
239+
let by_name { coqlib; coqcorelib; coq_native_compiler_default } name =
240+
match name with
241+
| "coqlib" -> Some (Value.path coqlib)
242+
| "coqcorelib" -> Option.map ~f:Value.path coqcorelib
243+
| "coq_native_compiler_default" ->
244+
Option.map ~f:Value.string coq_native_compiler_default
245+
| _ ->
246+
Code_error.raise
247+
"Unknown name was requested from coq_config"
248+
[ "name", Dyn.string name ]
249+
;;
253250

254251
let expand source macro artifacts_host =
255252
let s = Pform.Macro_invocation.Args.whole macro in
@@ -282,8 +279,7 @@ let expand source macro artifacts_host =
282279
| "version.suffix"
283280
| "version"
284281
| "ocaml-version" -> expand Version.make Version.by_name s
285-
| "coqlib" | "coqcorelib" | "coq_native_compiler_default" ->
286-
expand Config.make Config.by_name s
282+
| "coqlib" | "coqcorelib" | "coq_native_compiler_default" -> expand make by_name s
287283
| _ ->
288284
Code_error.raise "Unknown name was requested from coq_config" [ "name", Dyn.string s ]
289285
;;

src/dune_rules/coq/coq_config.mli

Lines changed: 16 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -40,29 +40,27 @@ module Version : sig
4040
val by_name : t -> string -> Value.t Option.t
4141
end
4242

43-
module Config : sig
44-
(** Data of a Coq configuration. *)
45-
type t
43+
(** Data of a Coq configuration. *)
44+
type t
4645

47-
(** [make ~coqc] runs coqc --config and returns the configuration data. Exceptionally, one
48-
of the following will happen:
46+
(** [make ~coqc] runs coqc --config and returns the configuration data. Exceptionally, one
47+
of the following will happen:
4948
50-
- Return [Error message] if coqc --config exits with a non-zero code.
51-
- Throw a user error if coqc --config is not parsable.
52-
- Throw an [Action.Prog.Not_found] exception if the coqc binary is not found. *)
53-
val make : coqc:Action.Prog.t -> (t, User_message.Style.t Pp.t) result Memo.t
49+
- Return [Error message] if coqc --config exits with a non-zero code.
50+
- Throw a user error if coqc --config is not parsable.
51+
- Throw an [Action.Prog.Not_found] exception if the coqc binary is not found. *)
52+
val make : coqc:Action.Prog.t -> (t, User_message.Style.t Pp.t) result Memo.t
5453

55-
(** [by_name t name] returns the value of the option [name] in the Coq
56-
configuration [t]. If the value is not available then [None] is returned.
57-
Throws a code error if an invalid [name] is requested.
54+
(** [by_name t name] returns the value of the option [name] in the Coq
55+
configuration [t]. If the value is not available then [None] is returned.
56+
Throws a code error if an invalid [name] is requested.
5857
59-
Currently supported names are:
58+
Currently supported names are:
6059
61-
- coqlib
62-
- coqcorelib
63-
- coq_native_compiler_default *)
64-
val by_name : t -> string -> Value.t Option.t
65-
end
60+
- coqlib
61+
- coqcorelib
62+
- coq_native_compiler_default *)
63+
val by_name : t -> string -> Value.t Option.t
6664

6765
val expand
6866
: Dune_lang.Template.Pform.t

src/dune_rules/coq/coq_path.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ let cmxs_directories t = t.cmxs_directories
2424
let stdlib t = t.stdlib
2525

2626
let config_path_exn coq_config key =
27-
Coq_config.Config.by_name coq_config key
27+
Coq_config.by_name coq_config key
2828
|> function
2929
| Some path ->
3030
path
@@ -47,7 +47,7 @@ let config_path_exn coq_config key =
4747
let config_path ~default coq_config key =
4848
Option.value
4949
~default:(Coq_config.Value.path default)
50-
(Coq_config.Config.by_name coq_config key)
50+
(Coq_config.by_name coq_config key)
5151
|> function
5252
| Coq_config.Value.Path p -> p (* We have found a path for key *)
5353
| path ->
@@ -175,7 +175,7 @@ let scan_vo root_path =
175175

176176
let of_coq_install coqc =
177177
let open Memo.O in
178-
let* coq_config = Coq_config.Config.make ~coqc:(Ok coqc) in
178+
let* coq_config = Coq_config.make ~coqc:(Ok coqc) in
179179
match coq_config with
180180
| Error msg ->
181181
User_warning.emit

src/dune_rules/coq/coq_rules.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -117,11 +117,11 @@ let select_native_mode ~sctx ~dir (buildable : Coq_stanza.Buildable.t) =
117117
then Memo.return Coq_mode.VoOnly
118118
else
119119
let* coqc = coqc ~sctx ~dir ~loc:buildable.loc in
120-
let+ config = Coq_config.Config.make ~coqc in
120+
let+ config = Coq_config.make ~coqc in
121121
(match config with
122122
| Error _ -> Coq_mode.VoOnly
123123
| Ok config ->
124-
(match Coq_config.Config.by_name config "coq_native_compiler_default" with
124+
(match Coq_config.by_name config "coq_native_compiler_default" with
125125
| Some (String "yes") | Some (String "ondemand") -> Coq_mode.Native
126126
| _ -> Coq_mode.VoOnly))
127127
;;

0 commit comments

Comments
 (0)