Skip to content

Commit 7f27f4e

Browse files
committed
Fixes from self-review
Signed-off-by: Shon Feder <[email protected]>
1 parent 0e163cb commit 7f27f4e

File tree

7 files changed

+21
-25
lines changed

7 files changed

+21
-25
lines changed

src/dune_lang/lib_kind.ml

Lines changed: 10 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -99,13 +99,14 @@ module Dune_file = struct
9999
| x -> x
100100
;;
101101

102-
let to_dyn x =
103-
let open Dyn in
104-
match x with
105-
| Normal -> variant "Normal" []
106-
| Parameter -> variant "Parameter" []
107-
| Ppx_deriver args -> variant "Ppx_deriver" [ Ppx_args.to_dyn args ]
108-
| Ppx_rewriter args -> variant "Ppx_rewriter" [ Ppx_args.to_dyn args ]
102+
let to_dyn x =
103+
let open Dyn in
104+
match x with
105+
| Normal -> variant "Normal" []
106+
| Parameter -> variant "Parameter" []
107+
| Ppx_deriver args -> variant "Ppx_deriver" [ Ppx_args.to_dyn args ]
108+
| Ppx_rewriter args -> variant "Ppx_rewriter" [ Ppx_args.to_dyn args ]
109+
;;
109110
end
110111

111112
type t =
@@ -117,24 +118,14 @@ let equal = Poly.equal
117118
let to_dyn x =
118119
let open Dyn in
119120
match x with
120-
| Dune_file t -> variant "Dune_file" [Dune_file.to_dyn t]
121+
| Dune_file t -> variant "Dune_file" [ Dune_file.to_dyn t ]
121122
| Virtual -> variant "Virtual" []
122123
;;
123124

124125
let decode =
125126
let open Decoder in
126127
(* TODO: Less code reuse with either? *)
127-
sum
128-
[ "normal", return (Dune_file Normal)
129-
; "parameter", return (Dune_file Parameter)
130-
; ( "ppx_deriver"
131-
, let+ args = Ppx_args.decode in
132-
Dune_file (Ppx_deriver args) )
133-
; ( "ppx_rewriter"
134-
, let+ args = Ppx_args.decode in
135-
Dune_file (Ppx_rewriter args) )
136-
; "virtual", return Virtual
137-
]
128+
map ~f:(fun k -> Dune_file k) Dune_file.decode <|> enum [ "virtual", Virtual ]
138129
;;
139130

140131
let encode t =

src/dune_lang/lib_kind.mli

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,11 @@ end
3434
(** Internal representation the of the possible kinds of libraries *)
3535
type t =
3636
| Dune_file of Dune_file.t
37+
(** A kind which is represented explicitly in the [kind] field of a dune
38+
library stanza.
39+
40+
The remaining variants are derived from other fields in the library
41+
stanza. *)
3742
| Virtual
3843

3944
val to_dyn : t Dyn.builder

src/dune_rules/dune_package.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -198,11 +198,11 @@ module Lib = struct
198198
(* Backward compatible support for dune-project files
199199
that include the [(virtual)] field. *)
200200
Lib_kind.Virtual
201-
| _incompatible_kind when virtual_ ->
201+
| incompatible_kind when virtual_ ->
202202
Code_error.raise
203203
"invalid combination of 'kind' and 'virtual' fields in library stanza of \
204204
dune-package file"
205-
[ "kind", Lib_kind.to_dyn kind; "virtual", Dyn.Bool virtual_ ]
205+
[ "kind", Lib_kind.to_dyn incompatible_kind; "virtual", Dyn.Bool virtual_ ]
206206
| otherwise -> otherwise
207207
and+ archives = mode_paths "archives"
208208
and+ plugins = mode_paths "plugins"

src/dune_rules/dune_package.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
(** Representation of dune-package files.
22
3-
dune-package files represent package data for the purposes of installation.
3+
dune-package files record package data for the purposes of installation.
44
They are not intended to be written or read by human users. *)
55

66
open Import

src/dune_rules/lib_info.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -368,7 +368,7 @@ let kind t = t.kind
368368
let default_implementation t = t.default_implementation
369369
let obj_dir t = t.obj_dir
370370
let virtual_ t = t.kind = Virtual
371-
let is_parameter t = t.kind = (Dune_file Parameter)
371+
let is_parameter t = t.kind = Dune_file Parameter
372372
let implements t = t.implements
373373
let synopsis t = t.synopsis
374374
let wrapped t = t.wrapped

src/dune_rules/ml_sources.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -365,7 +365,7 @@ let make_lib_modules
365365
in
366366
let kind : Modules_field_evaluator.kind =
367367
match lib.virtual_modules with
368-
| None -> if lib.kind = (Dune_file Parameter) then Parameter else Exe_or_normal_lib
368+
| None -> if Library.is_parameter lib then Parameter else Exe_or_normal_lib
369369
| Some virtual_modules -> Virtual { virtual_modules }
370370
in
371371
Memo.return (Resolve.return (kind, main_module_name, wrapped))

src/dune_rules/stanzas/library.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,7 @@ let decode =
135135
(match dune_file_kind with
136136
| Normal ->
137137
(* Libraries are virtual just in case [virtual_modules] are specified
138-
and they do not have an *non-normal* kind specified. *)
138+
and they do not have a *non-normal* kind specified. *)
139139
Virtual
140140
| (Parameter | Ppx_deriver _ | Ppx_rewriter _) as incompatable_kind ->
141141
User_error.raise

0 commit comments

Comments
 (0)