Skip to content

Commit fc0769e

Browse files
committed
refactor(coq): reintroduce Value type for coq_config
As was pointed out in my silly PR getting rid of it, it introduces an extra boxing that is unneeded. Signed-off-by: Ali Caglayan <alizter@gmail.com> <!-- ps-id: 2f6b0e94-1350-446a-810d-bfc6c34ae46e -->
1 parent 1513847 commit fc0769e

File tree

4 files changed

+36
-13
lines changed

4 files changed

+36
-13
lines changed

src/dune_rules/coq/coq_config.ml

Lines changed: 15 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,13 @@ end = struct
4444
let get_path t var = get t var |> Path.of_string
4545
end
4646

47+
module Value = struct
48+
type t =
49+
| Int of int
50+
| Path of Path.t
51+
| String of string
52+
end
53+
4754
module Version = struct
4855
module Num = struct
4956
type t =
@@ -83,9 +90,9 @@ module Version = struct
8390

8491
let by_name { major; minor; suffix } name =
8592
match name with
86-
| "major" -> Some (`Int major)
87-
| "minor" -> Some (`Int minor)
88-
| "suffix" -> Some (`String suffix)
93+
| "major" -> Some (Value.Int major)
94+
| "minor" -> Some (Value.Int minor)
95+
| "suffix" -> Some (Value.String suffix)
8996
| _ -> None
9097
end
9198

@@ -132,8 +139,8 @@ module Version = struct
132139
| "version.minor" -> Num.by_name version_num "minor"
133140
| "version.revision" -> Num.by_name version_num "revision"
134141
| "version.suffix" -> Num.by_name version_num "suffix"
135-
| "version" -> Some (`String version_string)
136-
| "ocaml-version" -> Some (`String ocaml_version_string)
142+
| "version" -> Some (Value.String version_string)
143+
| "ocaml-version" -> Some (Value.String ocaml_version_string)
137144
| _ -> None)
138145
end
139146

@@ -205,6 +212,7 @@ let by_name { version_info; coqlib; coq_native_compiler_default } name =
205212
| "version.suffix"
206213
| "version"
207214
| "ocaml-version" -> Version.by_name version_info name
208-
| "coqlib" -> Some (`Path coqlib)
209-
| "coq_native_compiler_default" -> Some (`String coq_native_compiler_default)
215+
| "coqlib" -> Some (Value.Path coqlib)
216+
| "coq_native_compiler_default" ->
217+
Some (Value.String coq_native_compiler_default)
210218
| _ -> None

src/dune_rules/coq/coq_config.mli

Lines changed: 17 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,5 +9,20 @@ val make : coqc:Action.Prog.t -> t Memo.t
99

1010
val make_opt : coqc:Action.Prog.t -> t Option.t Memo.t
1111

12-
val by_name :
13-
t -> string -> [> `Int of int | `Path of Path.t | `String of string ] Option.t
12+
module Value : sig
13+
type t =
14+
| Int of int
15+
| Path of Path.t
16+
| String of string
17+
end
18+
19+
(** [by_name t name] returns the value of the option [name] in the Coq
20+
configuration [t]. Currently supported names are:
21+
22+
- version.major
23+
- version.minor
24+
- version.revision
25+
- version.suffix
26+
- version
27+
- ocaml-version *)
28+
val by_name : t -> string -> Value.t Option.t

src/dune_rules/coq/coq_rules.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ let select_native_mode ~sctx ~dir (buildable : Coq_stanza.Buildable.t) =
2929
| None -> Coq_mode.VoOnly
3030
| Some config -> (
3131
match Coq_config.by_name config "coq_native_compiler_default" with
32-
| Some (`String "yes") | Some (`String "ondemand") -> Coq_mode.Native
32+
| Some (String "yes") | Some (String "ondemand") -> Coq_mode.Native
3333
| _ -> Coq_mode.VoOnly))
3434

3535
(* CR alizter: move this to Lib.DB *)

src/dune_rules/expander.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -627,9 +627,9 @@ let expand_pform_gen ~(context : Context.t) ~bindings ~dir ~source
627627
[ Pp.textf "Unknown Coq configuration variable %S" s ]
628628
| Some v -> (
629629
match v with
630-
| `Int x -> string (string_of_int x)
631-
| `String x -> string x
632-
| `Path x -> Value.L.paths [ x ])))))
630+
| Int x -> string (string_of_int x)
631+
| String x -> string x
632+
| Path x -> Value.L.paths [ x ])))))
633633

634634
(* Make sure to delay exceptions *)
635635
let expand_pform_gen ~context ~bindings ~dir ~source pform =

0 commit comments

Comments
 (0)