Skip to content

Commit e5f5338

Browse files
ejgallegoLysxia
andcommitted
[rocq] Remove need for coqc shims.
We remove the need for installing coqc shims, and adapt the test suite accordingly. There is one mayor caveat and one minor caveat: - the major caveat is that in builds composed with Rocq, dune will only search for `rocq`, but we don't inject a dependency on `rocqworker` which is also needed, but a private binary. This means that users should ensure manually `rocqworker` is built when using composed builds. We hope to fix this soon, in a different PR. - the minor caveat is that with `--display=short` we just now display the `rocq` name, not `rocq compile` or `rocq dep`. This can be also fixed in a different PR. Co-authored-by: Li-yao Xia <[email protected]> Signed-off-by: Emilio Jesus Gallego Arias <[email protected]>
1 parent d182251 commit e5f5338

File tree

51 files changed

+229
-236
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

51 files changed

+229
-236
lines changed

bin/rocq/rocqtop.ml

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ let term =
3737
Common.context_arg ~doc
3838
and+ rocqtop =
3939
let doc = Some "Run the given toplevel command instead of the default." in
40-
Arg.(value & opt string "coqtop" & info [ "toplevel" ] ~docv:"CMD" ~doc)
40+
Arg.(value & opt string "rocq" & info [ "toplevel" ] ~docv:"CMD" ~doc)
4141
and+ rocq_file_arg =
4242
Arg.(required & pos 0 (some string) None (Arg.info [] ~doc:None ~docv:"ROCQFILE"))
4343
and+ extra_args =
@@ -72,7 +72,7 @@ let term =
7272
| Some dir -> dir)
7373
|> Path.Build.append_local (Context.build_dir context)
7474
in
75-
let* rocqtop, args, env =
75+
let* rocqtop, rocq_arg, args, env =
7676
build_exn
7777
@@ fun () ->
7878
let open Memo.O in
@@ -145,22 +145,26 @@ let term =
145145
in
146146
Action_builder.evaluate_and_collect_facts deps_of
147147
in
148+
let real_binary, rocq_arg =
149+
if String.equal "rocq" rocqtop then "rocq", [ "top" ] else rocqtop, []
150+
in
151+
let* prog = Super_context.resolve_program_memo sctx ~dir ~loc:None real_binary in
152+
let prog = Action.Prog.ok_exn prog in
153+
let* () = Build_system.build_file prog in
148154
(* Get args *)
149155
let* (args, _) : string list * Dep.Fact.t Dep.Map.t =
150156
let* args = args in
151157
let dir = Path.external_ Path.External.initial_cwd in
152158
let args = Dune_rules.Command.expand ~dir (S args) in
153159
Action_builder.evaluate_and_collect_facts args.build
154160
in
155-
let* prog = Super_context.resolve_program_memo sctx ~dir ~loc:None rocqtop in
156-
let prog = Action.Prog.ok_exn prog in
157-
let* () = Build_system.build_file prog in
158161
let+ env = Super_context.context_env sctx in
159-
Path.to_string prog, args, env
162+
Path.to_string prog, rocq_arg, args, env
160163
in
164+
(* Careful about the first argument to "rocq" *)
161165
let args =
162166
let topfile = Path.to_absolute_filename (Path.build rocq_file_build) in
163-
("-topfile" :: topfile :: args) @ extra_args
167+
rocq_arg @ ("-topfile" :: topfile :: args) @ extra_args
164168
in
165169
Fiber.return (rocqtop, args, env)
166170
in

src/dune_rules/rocq/rocq_config.ml

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -78,8 +78,8 @@ end = struct
7878
;;
7979
end
8080

81-
let get_output_from_config_or_version ~(coqc : Action.Prog.t) ~what memo =
82-
match coqc with
81+
let get_output_from_config_or_version ~(rocq : Action.Prog.t) ~what memo =
82+
match rocq with
8383
| Ok coqc_path ->
8484
let open Memo.O in
8585
let+ output, exit_code = Memo.exec memo coqc_path in
@@ -170,10 +170,10 @@ module Version = struct
170170

171171
let version_memo = Memo.create "coq-and-ocaml-version" ~input:(module Path) impl_version
172172

173-
let make ~(coqc : Action.Prog.t) =
173+
let make ~(rocq : Action.Prog.t) =
174174
let open Memo.O in
175175
let+ version_output =
176-
get_output_from_config_or_version ~coqc ~what:"--print-version" version_memo
176+
get_output_from_config_or_version ~rocq ~what:"--print-version" version_memo
177177
in
178178
let open Result.O in
179179
let* version_output = version_output in
@@ -227,23 +227,23 @@ let impl_config bin =
227227

228228
let config_memo = Memo.create "rocq-config" ~input:(module Path) impl_config
229229

230-
let make ~(coqc : Action.Prog.t) =
230+
let make ~(rocq : Action.Prog.t) =
231231
let open Memo.O in
232232
let+ config_output =
233-
get_output_from_config_or_version ~coqc ~what:"--config" config_memo
233+
get_output_from_config_or_version ~rocq ~what:"--config" config_memo
234234
in
235235
let open Result.O in
236236
let* config_output = config_output in
237237
match Vars.of_lines config_output with
238238
| Ok vars ->
239239
(* EJGA: Note, this is still COQLIB and
240-
COQ_NATIVE_COMPILER_DEFAULT in both [coqc --config] and [rocq c
240+
COQ_NATIVE_COMPILER_DEFAULT in both [rocq --config] and [rocq c
241241
--config] ; so BEWARE ! *)
242242
let rocqlib = Vars.get_path vars "COQLIB" in
243243
let rocq_native_compiler_default = Vars.get_opt vars "COQ_NATIVE_COMPILER_DEFAULT" in
244244
Ok { rocqlib; rocq_native_compiler_default }
245245
| Error msg ->
246-
User_error.raise Pp.[ textf "Cannot parse output of coqc --config:"; msg ]
246+
User_error.raise Pp.[ textf "Cannot parse output of rocq --config:"; msg ]
247247
;;
248248

249249
let by_name { rocqlib; rocq_native_compiler_default } name =
@@ -260,14 +260,14 @@ let by_name { rocqlib; rocq_native_compiler_default } name =
260260
let expand source macro artifacts_host =
261261
let s = Pform.Macro_invocation.Args.whole macro in
262262
let open Memo.O in
263-
let* coqc = Artifacts.binary artifacts_host ~where:Original_path ~loc:None "coqc" in
263+
let* rocq = Artifacts.binary artifacts_host ~where:Original_path ~loc:None "rocq" in
264264
let expand m k s =
265-
let+ t = m ~coqc in
265+
let+ t = m ~rocq in
266266
match t with
267267
| Error msg ->
268268
User_error.raise
269269
~loc:(Dune_lang.Template.Pform.loc source)
270-
[ Pp.textf "Could not expand %%{rocq:%s} as running coqc failed." s; msg ]
270+
[ Pp.textf "Could not expand %%{rocq:%s} as running rocq failed." s; msg ]
271271
| Ok t ->
272272
(match k t s with
273273
| None ->

src/dune_rules/rocq/rocq_config.mli

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -29,14 +29,14 @@ module Version : sig
2929
(** Data of a Rocq version. *)
3030
type t
3131

32-
(** [make ~coqc] runs coqc --print-version and returns the version of Rocq
32+
(** [make ~rocq] runs rocq --print-version and returns the version of Rocq
3333
and the version of OCaml used to build Rocq.
3434
Exceptionally, one of the following will happen:
3535
36-
- Return [Error message] if coqc --print-version exits with a non-zero code.
37-
- Throw a user error if coqc --print-version is not parsable.
38-
- Throw an [Action.Prog.Not_found] exception if the coqc binary is not found. *)
39-
val make : coqc:Action.Prog.t -> (t, User_message.Style.t Pp.t) result Memo.t
36+
- Return [Error message] if rocq --print-version exits with a non-zero code.
37+
- Throw a user error if rocq --print-version is not parsable.
38+
- Throw an [Action.Prog.Not_found] exception if the rocq binary is not found. *)
39+
val make : rocq:Action.Prog.t -> (t, User_message.Style.t Pp.t) result Memo.t
4040

4141
(** [by_name t name] returns the value of the field [name] in the Rocq
4242
version [t]. If the value is not available then [None] is returned.
@@ -56,13 +56,13 @@ end
5656
(** Data of a Rocq configuration. *)
5757
type t
5858

59-
(** [make ~coqc] runs coqc --config and returns the configuration data. Exceptionally, one
59+
(** [make ~rocq] runs rocq --config and returns the configuration data. Exceptionally, one
6060
of the following will happen:
6161
62-
- Return [Error message] if coqc --config exits with a non-zero code.
63-
- Throw a user error if coqc --config is not parsable.
64-
- Throw an [Action.Prog.Not_found] exception if the coqc binary is not found. *)
65-
val make : coqc:Action.Prog.t -> (t, User_message.Style.t Pp.t) result Memo.t
62+
- Return [Error message] if rocq --config exits with a non-zero code.
63+
- Throw a user error if rocq --config is not parsable.
64+
- Throw an [Action.Prog.Not_found] exception if the rocq binary is not found. *)
65+
val make : rocq:Action.Prog.t -> (t, User_message.Style.t Pp.t) result Memo.t
6666

6767
(** [by_name t name] returns the value of the option [name] in the Rocq
6868
configuration [t]. If the value is not available then [None] is returned.

src/dune_rules/rocq/rocq_path.ml

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -36,11 +36,11 @@ let config_path_exn rocq_config key =
3636
(* This should never happen *)
3737
Code_error.raise "key is not a path" [ key, Rocq_config.Value.to_dyn path ])
3838
| None ->
39-
(* This happens if the output of coqc --config doesn't include the key *)
39+
(* This happens if the output of rocq --config doesn't include the key *)
4040
User_error.raise
4141
[ Pp.concat
4242
~sep:Pp.space
43-
[ Pp.text "key not found from"; User_message.command "coqc --config" ]
43+
[ Pp.text "key not found from"; User_message.command "rocq --config" ]
4444
|> Pp.hovbox
4545
; Pp.text key
4646
]
@@ -135,16 +135,16 @@ let scan_vo root_path =
135135
scan_path ~f ~acc ~prefix:() root_path
136136
;;
137137

138-
let of_rocq_install coqc =
138+
let of_rocq_install rocq =
139139
let open Memo.O in
140-
let* rocq_config = Rocq_config.make ~coqc:(Ok coqc) in
140+
let* rocq_config = Rocq_config.make ~rocq:(Ok rocq) in
141141
match rocq_config with
142142
| Error msg ->
143143
User_warning.emit
144144
[ Pp.concat
145145
~sep:Pp.space
146146
[ Pp.text "Skipping installed theories due to"
147-
; User_message.command "coqc --config"
147+
; User_message.command "rocq --config"
148148
; Pp.text "failure:"
149149
]
150150
|> Pp.hovbox
@@ -154,7 +154,7 @@ let of_rocq_install coqc =
154154
[ Pp.concat
155155
~sep:Pp.space
156156
[ Pp.text "Try running"
157-
; User_message.command "coqc --config"
157+
; User_message.command "rocq --config"
158158
; Pp.text "manually to see the error."
159159
]
160160
|> Pp.hovbox
@@ -178,18 +178,18 @@ let of_rocq_install coqc =
178178
Memo.return (corelib :: user_contrib)
179179
;;
180180

181-
let of_rocq_install coqc =
182-
(* If coqc was found in the _build directory then we must be composing
183-
with Coq and therefore cannot have any installed libs *)
184-
if Path.is_in_build_dir coqc then Memo.return [] else of_rocq_install coqc
181+
let of_rocq_install rocq =
182+
(* If rocq was found in the _build directory then we must be composing
183+
with Rocq and therefore cannot have any installed libs *)
184+
if Path.is_in_build_dir rocq then Memo.return [] else of_rocq_install rocq
185185
;;
186186

187187
let of_rocq_install context =
188188
let open Memo.O in
189-
let* coqc = Context.which context "coqc" in
190-
match coqc with
189+
let* rocq = Context.which context "rocq" in
190+
match rocq with
191191
| None -> Memo.return []
192-
| Some coqc -> of_rocq_install coqc
192+
| Some rocq -> of_rocq_install rocq
193193
;;
194194

195195
let of_env env =

src/dune_rules/rocq/rocq_rules.ml

Lines changed: 24 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -64,22 +64,22 @@ end = struct
6464
;;
6565
end
6666

67-
let coqc ~loc ~dir ~sctx =
67+
let rocq ~loc ~dir ~sctx =
6868
Super_context.resolve_program_memo
6969
sctx
70-
"coqc"
70+
"rocq"
7171
~where:Original_path
7272
~dir
7373
~loc:(Some loc)
74-
~hint:"opam install coq"
74+
~hint:"opam install rocq-runtime"
7575
;;
7676

7777
let select_native_mode ~sctx ~dir (buildable : Rocq_stanza.Buildable.t) =
7878
match buildable.mode with
7979
| Some x -> Memo.return x
8080
| None ->
81-
let* coqc = coqc ~sctx ~dir ~loc:buildable.loc in
82-
let+ config = Rocq_config.make ~coqc in
81+
let* rocq = rocq ~sctx ~dir ~loc:buildable.loc in
82+
let+ config = Rocq_config.make ~rocq in
8383
(match config with
8484
| Error _ -> Rocq_mode.VoOnly
8585
| Ok config ->
@@ -443,18 +443,13 @@ let setup_rocqdep_for_theory_rule
443443
rocqdep_flags ~dir ~stanza_rocqdep_flags ~expander
444444
in
445445
let rocqdep_flags =
446-
Command.Args.Dyn boot_flags :: Command.Args.dyn extra_rocqdep_flags :: file_flags
446+
Command.Args.A "dep"
447+
:: Command.Args.Dyn boot_flags
448+
:: Command.Args.dyn extra_rocqdep_flags
449+
:: file_flags
447450
in
448451
let stdout_to = dep_theory_file ~dir ~wrapper_name in
449-
let* coqdep =
450-
Super_context.resolve_program_memo
451-
sctx
452-
"coqdep"
453-
~dir
454-
~where:Original_path
455-
~loc:(Some loc)
456-
~hint:"opam install coq"
457-
in
452+
let* rocq = rocq ~loc ~sctx ~dir in
458453
(* Rocqdep has to be called in the stanza's directory *)
459454
Super_context.add_rule
460455
~loc
@@ -463,7 +458,7 @@ let setup_rocqdep_for_theory_rule
463458
(let open Action_builder.With_targets.O in
464459
Action_builder.with_no_targets mlpack_rule
465460
>>> Action_builder.(with_no_targets (goal source_rule))
466-
>>> Command.run ~dir:(Path.build dir) ~stdout_to coqdep rocqdep_flags)
461+
>>> Command.run ~dir:(Path.build dir) ~stdout_to rocq rocqdep_flags)
467462
;;
468463

469464
module Dep_map = Stdune.Map.Make (Path)
@@ -663,7 +658,7 @@ let setup_rocqc_rule
663658
let boot_flags = Resolve.Memo.read boot_type |> Action_builder.map ~f:Bootstrap.flags in
664659
(* TODO: merge with boot_type *)
665660
let per_file_flags = Per_file.match_ modules_flags rocq_module in
666-
let* coqc = coqc ~loc ~dir ~sctx in
661+
let* rocq = rocq ~loc ~dir ~sctx in
667662
let obj_files =
668663
Rocq_module.obj_files
669664
~wrapper_name
@@ -690,14 +685,18 @@ let setup_rocqc_rule
690685
rocq_module
691686
in
692687
let deps_of = deps_of ~dir ~boot_type ~wrapper_name ~mode rocq_module in
688+
let cflag = Command.Args.A "compile" in
693689
let open Action_builder.With_targets.O in
694690
Super_context.add_rule
695691
~loc
696692
~dir
697693
sctx
698694
(Action_builder.with_no_targets deps_of
699695
>>> Action_builder.With_targets.add ~file_targets
700-
@@ Command.run ~dir:(Path.build rocqc_dir) coqc (target_obj_files :: args)
696+
@@ Command.run
697+
~dir:(Path.build rocqc_dir)
698+
rocq
699+
(cflag :: target_obj_files :: args)
701700
(* The way we handle the transitive dependencies of .vo files is not safe for
702701
sandboxing *)
703702
>>| Action.Full.add_sandbox Sandbox_config.no_sandboxing)
@@ -739,15 +738,7 @@ let setup_rocqdoc_rules ~sctx ~dir ~theories_deps (s : Rocq_stanza.Theory.t) roc
739738
in
740739
fun mode ->
741740
let* () =
742-
let* rocqdoc =
743-
Super_context.resolve_program_memo
744-
sctx
745-
"coqdoc"
746-
~dir
747-
~where:Original_path
748-
~loc:(Some loc)
749-
~hint:"opam install coq"
750-
in
741+
let* rocq = rocq ~loc ~sctx ~dir in
751742
(let doc_dir = Rocq_doc.rocqdoc_directory ~mode ~obj_dir:dir ~name in
752743
let file_flags =
753744
let globs =
@@ -781,7 +772,8 @@ let setup_rocqdoc_rules ~sctx ~dir ~theories_deps (s : Rocq_stanza.Theory.t) roc
781772
in
782773
Expander.expand_and_eval_set expander s.rocqdoc_flags ~standard
783774
in
784-
[ Command.Args.S file_flags
775+
[ Command.Args.A "doc"
776+
; Command.Args.S file_flags
785777
; Command.Args.dyn extra_rocqdoc_flags
786778
; A mode_flag
787779
; A "-d"
@@ -797,7 +789,7 @@ let setup_rocqdoc_rules ~sctx ~dir ~theories_deps (s : Rocq_stanza.Theory.t) roc
797789
Command.run
798790
~sandbox:Sandbox_config.needs_sandboxing
799791
~dir:(Path.build dir)
800-
rocqdoc
792+
rocq
801793
file_flags
802794
|> Action_builder.With_targets.map
803795
~f:
@@ -1032,21 +1024,14 @@ let install_rules ~sctx ~dir s =
10321024
;;
10331025

10341026
let setup_rocqpp_rules ~sctx ~dir ({ loc; modules } : Rocq_stanza.Rocqpp.t) =
1035-
let* coqpp =
1036-
Super_context.resolve_program_memo
1037-
sctx
1038-
"coqpp"
1039-
~where:Original_path
1040-
~dir
1041-
~loc:(Some loc)
1042-
~hint:"opam install coq"
1027+
let* rocq = rocq ~loc ~sctx ~dir
10431028
and* mlg_files = Rocq_sources.mlg_files ~sctx ~dir ~modules in
10441029
let mlg_rule m =
10451030
let source = Path.build m in
10461031
let target = Path.Build.set_extension m ~ext:".ml" in
1047-
let args = [ Command.Args.Dep source; Hidden_targets [ target ] ] in
1032+
let args = [ Command.Args.A "pp-mlg"; Dep source; Hidden_targets [ target ] ] in
10481033
let build_dir = Super_context.context sctx |> Context.build_dir in
1049-
Command.run ~dir:(Path.build build_dir) coqpp args
1034+
Command.run ~dir:(Path.build build_dir) rocq args
10501035
in
10511036
List.rev_map ~f:mlg_rule mlg_files |> Super_context.add_rules ~loc ~dir sctx
10521037
;;
Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
11
$ dune build --display short --profile unsound --debug-dependency-path @all
2-
coqdep .basic.theory.d
3-
coqc Nbasic_foo.{cmi,cmxs},foo.{glob,vo}
4-
coqc Nbasic_bar.{cmi,cmxs},bar.{glob,vo}
2+
rocq .basic.theory.d
3+
rocq Nbasic_foo.{cmi,cmxs},foo.{glob,vo}
4+
rocq Nbasic_bar.{cmi,cmxs},bar.{glob,vo}

test/blackbox-tests/test-cases/rocq-native/base.t/run.t

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
$ dune build --display short --debug-dependency-path @all --always-show-command-line
2-
coqdep .basic.theory.d
3-
coqc Nbasic_foo.{cmi,cmxs},foo.{glob,vo}
4-
coqc Nbasic_bar.{cmi,cmxs},bar.{glob,vo}
2+
rocq .basic.theory.d
3+
rocq Nbasic_foo.{cmi,cmxs},foo.{glob,vo}
4+
rocq Nbasic_bar.{cmi,cmxs},bar.{glob,vo}
55

66
$ dune build --debug-dependency-path @default
77
lib: [

0 commit comments

Comments
 (0)