@@ -195,61 +195,58 @@ module Version = struct
195195 ;;
196196end
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
254251let 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;;
0 commit comments