Skip to content

Commit 835a44f

Browse files
authored
Make name and names fields optional when public_name or public_names are present (#1041)
Make name field optional when public_name is specified When name is omitted, it will be defaulted to public_name This feature is 1.1 only.
1 parent a13325e commit 835a44f

File tree

25 files changed

+150
-36
lines changed

25 files changed

+150
-36
lines changed

src/install_rules.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -304,7 +304,7 @@ module Gen(P : Params) = struct
304304
~f:(fun { SC.Installable. dir; stanza; kind = dir_kind; scope; _ } ->
305305
let dir_contents = Dir_contents.get sctx ~dir in
306306
match stanza with
307-
| Library ({ public = Some { package; sub_dir; name; _ }
307+
| Library ({ public = Some { package; sub_dir; name = (_, name); _ }
308308
; _ } as lib) ->
309309
List.map (lib_install_files ~dir ~sub_dir ~name lib ~scope
310310
~dir_kind ~dir_contents)

src/jbuild.ml

Lines changed: 93 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -640,20 +640,22 @@ end
640640

641641
module Public_lib = struct
642642
type t =
643-
{ name : string
643+
{ name : Loc.t * string
644644
; package : Package.t
645645
; sub_dir : string option
646646
}
647647

648+
let name t = snd t.name
649+
648650
let public_name_field =
649651
map_validate
650652
(let%map project = Dune_project.get_exn ()
651-
and name = field_o "public_name" string in
652-
(project, name))
653-
~f:(fun (project, name) ->
654-
match name with
653+
and loc_name = field_o "public_name" (located string) in
654+
(project, loc_name))
655+
~f:(fun (project, loc_name) ->
656+
match loc_name with
655657
| None -> Ok None
656-
| Some s ->
658+
| Some ((_, s) as loc_name) ->
657659
match String.split s ~on:'.' with
658660
| [] -> assert false
659661
| pkg :: rest ->
@@ -664,7 +666,7 @@ module Public_lib = struct
664666
; sub_dir =
665667
if rest = [] then None else
666668
Some (String.concat rest ~sep:"/")
667-
; name = s
669+
; name = loc_name
668670
})
669671
| Error _ as e -> e)
670672
end
@@ -805,7 +807,8 @@ module Library = struct
805807
let t =
806808
record
807809
(let%map buildable = Buildable.t
808-
and name = field "name" library_name
810+
and loc = loc
811+
and name = field_o "name" library_name
809812
and public = Public_lib.public_name_field
810813
and synopsis = field_o "synopsis" string
811814
and install_c_headers =
@@ -834,6 +837,23 @@ module Library = struct
834837
and project = Dune_project.get_exn ()
835838
and dune_version = Syntax.get_exn Stanza.syntax
836839
in
840+
let name =
841+
match name, public with
842+
| Some n, _ -> n
843+
| None, Some { name = (_loc, name) ; _ } ->
844+
if dune_version >= (1, 1) then
845+
name
846+
else
847+
of_sexp_error loc "name field cannot be omitted before version \
848+
1.1 of the dune language"
849+
| None, None ->
850+
of_sexp_error loc (
851+
if dune_version >= (1, 1) then
852+
"supply at least least one of name or public_name fields"
853+
else
854+
"name field is missing"
855+
)
856+
in
837857
{ name
838858
; public
839859
; synopsis
@@ -876,7 +896,7 @@ module Library = struct
876896
let best_name t =
877897
match t.public with
878898
| None -> t.name
879-
| Some p -> p.name
899+
| Some p -> snd p.name
880900
end
881901

882902
module Install_conf = struct
@@ -1020,7 +1040,19 @@ module Executables = struct
10201040
; buildable : Buildable.t
10211041
}
10221042

1023-
let common =
1043+
let pluralize s ~multi =
1044+
if multi then
1045+
s
1046+
else
1047+
s ^ "s"
1048+
1049+
let common
1050+
(* : (Loc.t * string) list option
1051+
* -> (Loc.t * string) list option
1052+
* -> multi:bool
1053+
* -> unit
1054+
* -> t * Install_conf.t option Sexp.Of_sexp.t *)
1055+
=
10241056
let%map buildable = Buildable.t
10251057
and (_ : bool) = field "link_executables" ~default:true
10261058
(Syntax.deleted_in Stanza.syntax (1, 0) >>> bool)
@@ -1040,8 +1072,33 @@ module Executables = struct
10401072
(loc, s))
10411073
and project = Dune_project.get_exn ()
10421074
and file_kind = Stanza.file_kind ()
1075+
and dune_syntax = Syntax.get_exn Stanza.syntax
1076+
and loc = loc
10431077
in
10441078
fun names public_names ~multi ->
1079+
let names =
1080+
match names, public_names with
1081+
| Some names, _ -> names
1082+
| None, Some public_names ->
1083+
if dune_syntax >= (1, 1) then
1084+
List.map public_names ~f:(fun (loc, p) ->
1085+
match p with
1086+
| None ->
1087+
of_sexp_error loc "This executable must have a name field"
1088+
| Some s -> (loc, s))
1089+
else
1090+
of_sexp_errorf loc
1091+
"%s field may not be omitted before dune version 1.1"
1092+
(pluralize ~multi "name")
1093+
| None, None ->
1094+
if dune_syntax >= (1, 1) then
1095+
of_sexp_errorf loc "either the %s or the %s field must be present"
1096+
(pluralize ~multi "name")
1097+
(pluralize ~multi "public_name")
1098+
else
1099+
of_sexp_errorf loc "field %s is missing"
1100+
(pluralize ~multi "name")
1101+
in
10451102
let t =
10461103
{ names
10471104
; link_flags
@@ -1051,7 +1108,10 @@ module Executables = struct
10511108
}
10521109
in
10531110
let has_public_name =
1054-
List.exists ~f:Option.is_some public_names
1111+
(* user could omit public names by avoiding the field or writing - *)
1112+
match public_names with
1113+
| None -> false
1114+
| Some pns -> List.exists ~f:(fun (_, n) -> Option.is_some n) pns
10551115
in
10561116
let to_install =
10571117
match Link_mode.Set.best_install_mode t.modes with
@@ -1073,8 +1133,13 @@ module Executables = struct
10731133
| Native | Best -> ".exe"
10741134
| Byte -> ".bc"
10751135
in
1136+
let public_names =
1137+
match public_names with
1138+
| None -> List.map names ~f:(fun _ -> (Loc.none, None))
1139+
| Some pns -> pns
1140+
in
10761141
List.map2 names public_names
1077-
~f:(fun (_, name) pub ->
1142+
~f:(fun (_, name) (_, pub) ->
10781143
match pub with
10791144
| None -> None
10801145
| Some pub -> Some ({ Install_conf.
@@ -1114,35 +1179,40 @@ module Executables = struct
11141179
(t, Some { Install_conf. section = Bin; files; package })
11151180

11161181
let public_name =
1117-
string >>| function
1182+
located string >>| fun (loc, s) ->
1183+
(loc
1184+
, match s with
11181185
| "-" -> None
1119-
| s -> Some s
1186+
| s -> Some s)
11201187

11211188
let multi =
11221189
record
11231190
(let%map names, public_names =
11241191
map_validate
1125-
(let%map names = field "names" (list (located string))
1192+
(let%map names = field_o "names" (list (located string))
11261193
and pub_names = field_o "public_names" (list public_name) in
11271194
(names, pub_names))
11281195
~f:(fun (names, public_names) ->
1129-
match public_names with
1130-
| None -> Ok (names, List.map names ~f:(fun _ -> None))
1131-
| Some public_names ->
1196+
match names, public_names with
1197+
| Some names, Some public_names ->
11321198
if List.length public_names = List.length names then
1133-
Ok (names, public_names)
1199+
Ok (Some names, Some public_names)
11341200
else
11351201
Error "The list of public names must be of the same \
1136-
length as the list of names")
1202+
length as the list of names"
1203+
| names, public_names -> Ok (names, public_names))
11371204
and f = common in
11381205
f names public_names ~multi:true)
11391206

11401207
let single =
11411208
record
1142-
(let%map name = field "name" (located string)
1143-
and public_name = field_o "public_name" string
1209+
(let%map name = field_o "name" (located string)
1210+
and public_name = field_o "public_name" (located string)
11441211
and f = common in
1145-
f [name] [public_name] ~multi:false)
1212+
f (Option.map name ~f:List.singleton)
1213+
(Option.map public_name ~f:(fun (loc, s) ->
1214+
[loc, Some s]))
1215+
~multi:false)
11461216
end
11471217

11481218
module Rule = struct

src/jbuild.mli

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -137,11 +137,13 @@ end
137137

138138
module Public_lib : sig
139139
type t =
140-
{ name : string (** Full public name *)
141-
; package : Package.t (** Package it is part of *)
142-
; sub_dir : string option (** Subdirectory inside the installation
143-
directory *)
140+
{ name : Loc.t * string (** Full public name *)
141+
; package : Package.t (** Package it is part of *)
142+
; sub_dir : string option (** Subdirectory inside the installation
143+
directory *)
144144
}
145+
146+
val name : t -> string
145147
end
146148

147149
module Sub_system_info : sig

src/lib.ml

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -988,11 +988,12 @@ module DB = struct
988988
| None ->
989989
[(conf.name, Resolve_result.Found info)]
990990
| Some p ->
991-
if p.name = conf.name then
992-
[(p.name, Found info)]
991+
let name = Jbuild.Public_lib.name p in
992+
if name = conf.name then
993+
[(name, Found info)]
993994
else
994-
[ p.name , Found info
995-
; conf.name, Redirect (None, p.name)
995+
[ name , Found info
996+
; conf.name, Redirect (None, name)
996997
])
997998
|> String.Map.of_list
998999
|> function
@@ -1003,7 +1004,7 @@ module DB = struct
10031004
if name = conf.name ||
10041005
match conf.public with
10051006
| None -> false
1006-
| Some p -> name = p.name
1007+
| Some p -> name = Jbuild.Public_lib.name p
10071008
then Some conf.buildable.loc
10081009
else None)
10091010
with

src/scope.ml

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -78,7 +78,7 @@ module DB = struct
7878
List.filter_map internal_libs ~f:(fun (_dir, lib) ->
7979
match lib.public with
8080
| None -> None
81-
| Some p -> Some (p.name, lib.project))
81+
| Some p -> Some (Jbuild.Public_lib.name p, lib.project))
8282
|> String.Map.of_list
8383
|> function
8484
| Ok x -> x
@@ -87,7 +87,8 @@ module DB = struct
8787
List.filter_map internal_libs ~f:(fun (_dir, lib) ->
8888
match lib.public with
8989
| None -> None
90-
| Some p -> Option.some_if (name = p.name) lib.buildable.loc)
90+
| Some p -> Option.some_if (name = Jbuild.Public_lib.name p)
91+
lib.buildable.loc)
9192
with
9293
| [] | [_] -> assert false
9394
| loc1 :: loc2 :: _ ->

src/super_context.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,8 @@ let internal_lib_names t =
7777
String.Set.add
7878
(match lib.public with
7979
| None -> acc
80-
| Some { name; _ } -> String.Set.add acc name)
80+
| Some { name = (_, name); _ } ->
81+
String.Set.add acc name)
8182
lib.name
8283
| _ -> acc))
8384

test/blackbox-tests/dune.inc

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -468,6 +468,14 @@
468468
test-cases/no-installable-mode
469469
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))
470470

471+
(alias
472+
(name no-name-field)
473+
(deps (package dune) (source_tree test-cases/no-name-field))
474+
(action
475+
(chdir
476+
test-cases/no-name-field
477+
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))
478+
471479
(alias
472480
(name null-dep)
473481
(deps (package dune) (source_tree test-cases/null-dep))
@@ -782,6 +790,7 @@
782790
(alias misc)
783791
(alias multiple-private-libs)
784792
(alias no-installable-mode)
793+
(alias no-name-field)
785794
(alias null-dep)
786795
(alias ocaml-config-macro)
787796
(alias ocaml-syntax)
@@ -868,6 +877,7 @@
868877
(alias meta-gen)
869878
(alias misc)
870879
(alias no-installable-mode)
880+
(alias no-name-field)
871881
(alias null-dep)
872882
(alias ocaml-config-macro)
873883
(alias ocaml-syntax)
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
(executables (public_names foo bar))
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
(lang dune 1.0)

test/blackbox-tests/test-cases/no-name-field/no-name-exes-syntax-1-0/foo.opam

Whitespace-only changes.

0 commit comments

Comments
 (0)