Skip to content

Commit 923ab23

Browse files
committed
Allow dash in dune init project name
Signed-off-by: ArthurW <[email protected]>
1 parent e43cb9d commit 923ab23

File tree

5 files changed

+133
-53
lines changed

5 files changed

+133
-53
lines changed

bin/dune_init.ml

+25-20
Original file line numberDiff line numberDiff line change
@@ -245,20 +245,27 @@ module Component = struct
245245
module Common = struct
246246
type t =
247247
{ name : Dune_lang.Atom.t
248+
; public : Public_name.t option
248249
; libraries : Dune_lang.Atom.t list
249250
; pps : Dune_lang.Atom.t list
250251
}
252+
253+
let package_name common =
254+
let name =
255+
match common.public with
256+
| None -> Dune_lang.Atom.to_string common.name
257+
| Some public -> Public_name.to_string public
258+
in
259+
Package.Name.of_string name
260+
;;
251261
end
252262

253263
module Executable = struct
254-
type t = { public : Public_name.t option }
264+
type t = unit
255265
end
256266

257267
module Library = struct
258-
type t =
259-
{ public : Public_name.t option
260-
; inline_tests : bool
261-
}
268+
type t = { inline_tests : bool }
262269
end
263270

264271
module Project = struct
@@ -355,11 +362,11 @@ module Component = struct
355362

356363
let public_name_field = Encoder.field_o "public_name" Public_name.encode
357364

358-
let executable (common : Options.Common.t) (options : Options.Executable.t) =
359-
make "executable" common [ public_name_field options.public ]
365+
let executable (common : Options.Common.t) (() : Options.Executable.t) =
366+
make "executable" common [ public_name_field common.public ]
360367
;;
361368

362-
let library (common : Options.Common.t) { Options.Library.inline_tests; public } =
369+
let library (common : Options.Common.t) { Options.Library.inline_tests } =
363370
check_module_name common.name;
364371
let common =
365372
if inline_tests
@@ -370,7 +377,10 @@ module Component = struct
370377
{ common with pps })
371378
else common
372379
in
373-
make "library" common [ public_name_field public; Field.inline_tests inline_tests ]
380+
make
381+
"library"
382+
common
383+
[ public_name_field common.public; Field.inline_tests inline_tests ]
374384
;;
375385

376386
let test common (() : Options.Test.t) = make "test" common []
@@ -385,7 +395,7 @@ module Component = struct
385395
let cst =
386396
let package =
387397
Package.create
388-
~name:(Package.Name.of_string (Atom.to_string common.name))
398+
~name:(Options.Common.package_name common)
389399
~loc:Loc.none
390400
~version:None
391401
~conflicts:[]
@@ -499,8 +509,8 @@ module Component = struct
499509
let lib_target =
500510
src
501511
{ context = { context with dir = Path.relative dir "lib" }
502-
; options = { public = None; inline_tests = options.inline_tests }
503-
; common
512+
; options = { inline_tests = options.inline_tests }
513+
; common = { common with public = None }
504514
}
505515
in
506516
let test_target =
@@ -516,7 +526,7 @@ module Component = struct
516526
let libraries = Stanza_cst.add_to_list_set common.name common.libraries in
517527
bin
518528
{ context = { context with dir = Path.relative dir "bin" }
519-
; options = { public = Some (Public_name.of_name_exn common.name) }
529+
; options = ()
520530
; common = { common with libraries; name = Dune_lang.Atom.of_string "main" }
521531
}
522532
in
@@ -527,10 +537,7 @@ module Component = struct
527537
let lib_target =
528538
src
529539
{ context = { context with dir = Path.relative dir "lib" }
530-
; options =
531-
{ public = Some (Public_name.of_name_exn common.name)
532-
; inline_tests = options.inline_tests
533-
}
540+
; options = { inline_tests = options.inline_tests }
534541
; common
535542
}
536543
in
@@ -548,13 +555,11 @@ module Component = struct
548555
let proj ({ common; options; _ } as opts : Options.Project.t Options.t) =
549556
let ({ template; pkg; _ } : Options.Project.t) = options in
550557
let dir = Path.Source.root in
551-
let name =
552-
Package.Name.parse_string_exn (Loc.none, Dune_lang.Atom.to_string common.name)
553-
in
554558
let proj_target =
555559
let package_files =
556560
match (pkg : Options.Project.Pkg.t) with
557561
| Opam ->
562+
let name = Options.Common.package_name common in
558563
let opam_file = Path.source @@ Package_name.file name ~dir in
559564
[ File.make_text (Path.parent_exn opam_file) (Path.basename opam_file) "" ]
560565
| Esy -> [ File.make_text (Path.source dir) "package.json" "" ]

bin/dune_init.mli

+4-5
Original file line numberDiff line numberDiff line change
@@ -32,22 +32,21 @@ module Component : sig
3232
module Common : sig
3333
type t =
3434
{ name : Dune_lang.Atom.t
35+
; public : Public_name.t option
3536
; libraries : Dune_lang.Atom.t list
3637
; pps : Dune_lang.Atom.t list
3738
}
3839
end
3940

4041
(** Options for executable components *)
4142
module Executable : sig
42-
type t = { public : Public_name.t option }
43+
(** NOTE: no options supported yet *)
44+
type t = unit
4345
end
4446

4547
(** Options for library components *)
4648
module Library : sig
47-
type t =
48-
{ public : Public_name.t option
49-
; inline_tests : bool
50-
}
49+
type t = { inline_tests : bool }
5150
end
5251

5352
(** Options for test components *)

bin/init.ml

+76-28
Original file line numberDiff line numberDiff line change
@@ -31,8 +31,28 @@ let component_name_parser s =
3131
Ok atom
3232
;;
3333

34+
let project_name_parser s =
35+
(* TODO refactor Dune_project_name to be Stringlike *)
36+
match Dune_project_name.named Loc.none s with
37+
| v -> Ok v
38+
| exception User_error.E _ ->
39+
User_error.make
40+
[ Pp.textf "invalid project name `%s'" s
41+
; Pp.text
42+
"Project names must start with a letter and be composed only of letters, \
43+
numbers, '-' or '_'"
44+
]
45+
|> User_message.to_string
46+
|> fun m -> Error (`Msg m)
47+
;;
48+
49+
let project_name_printer ppf p =
50+
Format.pp_print_string ppf (Dune_project_name.to_string_hum p)
51+
;;
52+
3453
let atom_conv = Arg.conv (atom_parser, atom_printer)
3554
let component_name_conv = Arg.conv (component_name_parser, atom_printer)
55+
let project_name_conv = Arg.conv (project_name_parser, project_name_printer)
3656

3757
(** {2 Status reporting} *)
3858

@@ -48,22 +68,6 @@ let print_completion kind name =
4868

4969
(** {1 CLI} *)
5070

51-
let common : Component.Options.Common.t Term.t =
52-
let+ name =
53-
let docv = "NAME" in
54-
Arg.(required & pos 0 (some component_name_conv) None & info [] ~docv)
55-
and+ libraries =
56-
let docv = "LIBRARIES" in
57-
let doc = "A comma separated list of libraries on which the component depends" in
58-
Arg.(value & opt (list atom_conv) [] & info [ "libs" ] ~docv ~doc)
59-
and+ pps =
60-
let docv = "PREPROCESSORS" in
61-
let doc = "A comma separated list of ppx preprocessors used by the component" in
62-
Arg.(value & opt (list atom_conv) [] & info [ "ppx" ] ~docv ~doc)
63-
in
64-
{ Component.Options.Common.name; libraries; pps }
65-
;;
66-
6771
let path =
6872
let docv = "PATH" in
6973
Arg.(value & pos 1 (some string) None & info [] ~docv)
@@ -89,9 +93,9 @@ module Public_name = struct
8993
| Public_name p -> Public_name.to_string p
9094
;;
9195

92-
let public_name (common : Component.Options.Common.t) = function
96+
let public_name default_name = function
9397
| None -> None
94-
| Some Use_name -> Some (Public_name.of_name_exn common.name)
98+
| Some Use_name -> Some (Public_name.of_name_exn default_name)
9599
| Some (Public_name n) -> Some n
96100
;;
97101

@@ -111,6 +115,18 @@ module Public_name = struct
111115
;;
112116
end
113117

118+
let libraries =
119+
let docv = "LIBRARIES" in
120+
let doc = "A comma separated list of libraries on which the component depends" in
121+
Arg.(value & opt (list atom_conv) [] & info [ "libs" ] ~docv ~doc)
122+
;;
123+
124+
let pps =
125+
let docv = "PREPROCESSORS" in
126+
let doc = "A comma separated list of ppx preprocessors used by the component" in
127+
Arg.(value & opt (list atom_conv) [] & info [ "ppx" ] ~docv ~doc)
128+
;;
129+
114130
let public : Public_name.t option Term.t =
115131
let docv = "PUBLIC_NAME" in
116132
let doc =
@@ -123,6 +139,38 @@ let public : Public_name.t option Term.t =
123139
& info [ "public" ] ~docv ~doc)
124140
;;
125141

142+
let common : Component.Options.Common.t Term.t =
143+
let+ name =
144+
let docv = "NAME" in
145+
Arg.(required & pos 0 (some component_name_conv) None & info [] ~docv)
146+
and+ public = public
147+
and+ libraries = libraries
148+
and+ pps = pps in
149+
let public = Public_name.public_name name public in
150+
{ Component.Options.Common.name; public; libraries; pps }
151+
;;
152+
153+
let project_common : Component.Options.Common.t Term.t =
154+
let+ project_name =
155+
let docv = "NAME" in
156+
Arg.(required & pos 0 (some project_name_conv) None & info [] ~docv)
157+
and+ libraries = libraries
158+
and+ pps = pps in
159+
let public = Dune_project_name.to_string_hum project_name in
160+
let name =
161+
String.map
162+
~f:(function
163+
| '-' -> '_'
164+
| c -> c)
165+
public
166+
|> Dune_lang.Atom.of_string
167+
in
168+
let public =
169+
Some (Dune_lang.Atom.of_string public |> Dune_init.Public_name.of_name_exn)
170+
in
171+
{ Component.Options.Common.name; public; libraries; pps }
172+
;;
173+
126174
let inline_tests : bool Term.t =
127175
let docv = "USE_INLINE_TESTS" in
128176
let doc =
@@ -140,10 +188,8 @@ let executable =
140188
let kind = "executable" in
141189
Cmd.v (Cmd.info kind ~doc ~man)
142190
@@ let+ context = context_cwd
143-
and+ common = common
144-
and+ public = public in
145-
let public = Public_name.public_name common public in
146-
Component.init (Executable { context; common; options = { public } });
191+
and+ common = common in
192+
Component.init (Executable { context; common; options = () });
147193
print_completion kind common.name
148194
;;
149195

@@ -154,10 +200,8 @@ let library =
154200
Cmd.v (Cmd.info kind ~doc ~man)
155201
@@ let+ context = context_cwd
156202
and+ common = common
157-
and+ public = public
158203
and+ inline_tests = inline_tests in
159-
let public = Public_name.public_name common public in
160-
Component.init (Library { context; common; options = { public; inline_tests } });
204+
Component.init (Library { context; common; options = { inline_tests } });
161205
print_completion kind common.name
162206
;;
163207

@@ -187,7 +231,7 @@ let project =
187231
Cmd.v (Cmd.info "project" ~doc ~man)
188232
@@ let+ common_builder = Builder.term
189233
and+ path = path
190-
and+ common = common
234+
and+ common = project_common
191235
and+ inline_tests = inline_tests
192236
and+ template =
193237
let docv = "PROJECT_KIND" in
@@ -215,9 +259,13 @@ let project =
215259
& opt (some (enum Component.Options.Project.Pkg.commands)) None
216260
& info [ "pkg" ] ~docv ~doc)
217261
in
262+
let name =
263+
match common.public with
264+
| None -> Dune_lang.Atom.to_string common.name
265+
| Some public -> Dune_init.Public_name.to_string public
266+
in
218267
let context =
219268
let init_context = Init_context.make path in
220-
let name = Dune_lang.Atom.to_string common.name in
221269
let root =
222270
match path with
223271
(* If a path is given, we use that for the root during project
@@ -235,7 +283,7 @@ let project =
235283
in
236284
Component.init
237285
(Project { context; common; options = { template; inline_tests; pkg } });
238-
print_completion "project" common.name
286+
print_completion "project" (Dune_lang.Atom.of_string name)
239287
;;
240288

241289
let group =

doc/changes/11402.md

+1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
- Allow dash in dune init project name (#11402, @art-w, reported by @saroupille)
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,27 @@
1+
Dash are allowed in project names and should be accepted:
2+
3+
$ dune init project dash-exe
4+
Entering directory 'dash-exe'
5+
Success: initialized project component named dash-exe
6+
Leaving directory 'dash-exe'
7+
$ cd dash-exe && dune build
8+
9+
$ dune init project dash-lib --kind=library
10+
Entering directory 'dash-lib'
11+
Success: initialized project component named dash-lib
12+
Leaving directory 'dash-lib'
13+
$ cd dash-lib && dune build
14+
15+
Invalid project names should still be rejected:
16+
17+
$ dune init project invalid.name
18+
dune: NAME argument: invalid project name `invalid.name'
19+
Project names must start with a letter and be composed only of
20+
letters,
21+
numbers, '-' or '_'
22+
Usage: dune init project [OPTION]… NAME [PATH]
23+
Try 'dune init project --help' or 'dune --help' for more information.
24+
[1]
25+
$ ls invalid.name
26+
ls: cannot access 'invalid.name': No such file or directory
27+
[2]

0 commit comments

Comments
 (0)