@@ -31,8 +31,28 @@ let component_name_parser s =
31
31
Ok atom
32
32
;;
33
33
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
+
34
53
let atom_conv = Arg. conv (atom_parser, atom_printer)
35
54
let component_name_conv = Arg. conv (component_name_parser, atom_printer)
55
+ let project_name_conv = Arg. conv (project_name_parser, project_name_printer)
36
56
37
57
(* * {2 Status reporting} *)
38
58
@@ -48,22 +68,6 @@ let print_completion kind name =
48
68
49
69
(* * {1 CLI} *)
50
70
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
-
67
71
let path =
68
72
let docv = " PATH" in
69
73
Arg. (value & pos 1 (some string ) None & info [] ~docv )
@@ -89,9 +93,9 @@ module Public_name = struct
89
93
| Public_name p -> Public_name. to_string p
90
94
;;
91
95
92
- let public_name ( common : Component.Options.Common.t ) = function
96
+ let public_name default_name = function
93
97
| 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 )
95
99
| Some (Public_name n ) -> Some n
96
100
;;
97
101
@@ -111,6 +115,18 @@ module Public_name = struct
111
115
;;
112
116
end
113
117
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
+
114
130
let public : Public_name.t option Term.t =
115
131
let docv = " PUBLIC_NAME" in
116
132
let doc =
@@ -123,6 +139,38 @@ let public : Public_name.t option Term.t =
123
139
& info [ " public" ] ~docv ~doc )
124
140
;;
125
141
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
+
126
174
let inline_tests : bool Term.t =
127
175
let docv = " USE_INLINE_TESTS" in
128
176
let doc =
@@ -140,10 +188,8 @@ let executable =
140
188
let kind = " executable" in
141
189
Cmd. v (Cmd. info kind ~doc ~man )
142
190
@@ 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 = () });
147
193
print_completion kind common.name
148
194
;;
149
195
@@ -154,10 +200,8 @@ let library =
154
200
Cmd. v (Cmd. info kind ~doc ~man )
155
201
@@ let + context = context_cwd
156
202
and + common = common
157
- and + public = public
158
203
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 } });
161
205
print_completion kind common.name
162
206
;;
163
207
@@ -187,7 +231,7 @@ let project =
187
231
Cmd. v (Cmd. info " project" ~doc ~man )
188
232
@@ let + common_builder = Builder. term
189
233
and + path = path
190
- and + common = common
234
+ and + common = project_common
191
235
and + inline_tests = inline_tests
192
236
and + template =
193
237
let docv = " PROJECT_KIND" in
@@ -215,9 +259,13 @@ let project =
215
259
& opt (some (enum Component.Options.Project.Pkg. commands)) None
216
260
& info [ " pkg" ] ~docv ~doc )
217
261
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
218
267
let context =
219
268
let init_context = Init_context. make path in
220
- let name = Dune_lang.Atom. to_string common.name in
221
269
let root =
222
270
match path with
223
271
(* If a path is given, we use that for the root during project
@@ -235,7 +283,7 @@ let project =
235
283
in
236
284
Component. init
237
285
(Project { context; common; options = { template; inline_tests; pkg } });
238
- print_completion " project" common. name
286
+ print_completion " project" ( Dune_lang.Atom. of_string name)
239
287
;;
240
288
241
289
let group =
0 commit comments