Skip to content

Commit 78717ba

Browse files
committed
fix(init): parse --public as a package name
Fixes #7108 Signed-off-by: Etienne Millon <me@emillon.org>
1 parent 61df58f commit 78717ba

File tree

10 files changed

+142
-64
lines changed

10 files changed

+142
-64
lines changed

bin/dune_init.ml

Lines changed: 66 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -195,6 +195,64 @@ module Init_context = struct
195195
;;
196196
end
197197

198+
module Public_name = struct
199+
module Pkg = Dune_lang.Package_name.Opam_compatible
200+
201+
module T = struct
202+
type t =
203+
{ pkg : Pkg.t
204+
; sub : string list
205+
}
206+
207+
let module_ = "Dune_init.Public_name"
208+
let description = "public name"
209+
210+
let description_of_valid_string =
211+
let open Pp.O in
212+
Some
213+
(Pp.text
214+
"Public names are composed of an opam package name and optional dot-separated \
215+
string suffixes."
216+
++ Pp.newline
217+
++ Pkg.description_of_valid_string)
218+
;;
219+
220+
let split s =
221+
match String.split s ~on:'.' with
222+
| [] -> assert false
223+
| pkg_s :: sub -> pkg_s, sub
224+
;;
225+
226+
let join pkg_s sub = String.concat ~sep:"." (pkg_s :: sub)
227+
228+
let make_valid s =
229+
let pkg_s, sub = split s in
230+
let pkg_fixed = Pkg.make_valid pkg_s in
231+
join pkg_fixed sub
232+
;;
233+
234+
let hint_valid = Some make_valid
235+
236+
let of_string_opt s =
237+
let open Option.O in
238+
let pkg_s, sub = split s in
239+
let+ pkg = Pkg.of_string_opt pkg_s in
240+
{ pkg; sub }
241+
;;
242+
243+
let to_string { pkg; sub } = join (Pkg.to_string pkg) sub
244+
end
245+
246+
include T
247+
include Dune_util.Stringlike.Make (T)
248+
249+
let of_name_exn name =
250+
let s = Dune_lang.Atom.to_string name in
251+
let pkg = Pkg.of_string_user_error (Loc.none, s) |> User_error.ok_exn in
252+
{ pkg; sub = [] }
253+
;;
254+
end
255+
198256
module Component = struct
199257
module Options = struct
200258
module Common = struct
@@ -206,12 +264,12 @@ module Component = struct
206264
end
207265

208266
module Executable = struct
209-
type t = { public : Dune_lang.Atom.t option }
267+
type t = { public : Public_name.t option }
210268
end
211269

212270
module Library = struct
213271
type t =
214-
{ public : Dune_lang.Atom.t option
272+
{ public : Public_name.t option
215273
; inline_tests : bool
216274
}
217275
end
@@ -308,8 +366,7 @@ module Component = struct
308366
if List.mem ~equal:Dune_lang.Atom.equal set elem then set else elem :: set
309367
;;
310368

311-
let public_name_encoder atom = Atom atom
312-
let public_name_field = Encoder.field_o "public_name" public_name_encoder
369+
let public_name_field = Encoder.field_o "public_name" Public_name.encode
313370

314371
let executable (common : Options.Common.t) (options : Options.Executable.t) =
315372
make "executable" common [ public_name_field options.public ]
@@ -438,7 +495,7 @@ module Component = struct
438495
let libraries = Stanza_cst.add_to_list_set common.name common.libraries in
439496
bin
440497
{ context = { context with dir = Path.relative dir "bin" }
441-
; options = { public = Some common.name }
498+
; options = { public = Some (Public_name.of_name_exn common.name) }
442499
; common = { common with libraries; name = Dune_lang.Atom.of_string "main" }
443500
}
444501
in
@@ -449,7 +506,10 @@ module Component = struct
449506
let lib_target =
450507
src
451508
{ context = { context with dir = Path.relative dir "lib" }
452-
; options = { public = Some common.name; inline_tests = options.inline_tests }
509+
; options =
510+
{ public = Some (Public_name.of_name_exn common.name)
511+
; inline_tests = options.inline_tests
512+
}
453513
; common
454514
}
455515
in

bin/dune_init.mli

Lines changed: 8 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,12 @@ module Init_context : sig
1212
val make : string option -> t Memo.t
1313
end
1414

15+
module Public_name : sig
16+
include Dune_util.Stringlike
17+
18+
val of_name_exn : Dune_lang.Atom.t -> t
19+
end
20+
1521
(** A [Component.t] is a set of files that can be built or included as part of a
1622
build. *)
1723
module Component : sig
@@ -28,13 +34,13 @@ module Component : sig
2834

2935
(** Options for executable components *)
3036
module Executable : sig
31-
type t = { public : Dune_lang.Atom.t option }
37+
type t = { public : Public_name.t option }
3238
end
3339

3440
(** Options for library components *)
3541
module Library : sig
3642
type t =
37-
{ public : Dune_lang.Atom.t option
43+
{ public : Public_name.t option
3844
; inline_tests : bool
3945
}
4046
end

bin/init.ml

Lines changed: 10 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -79,23 +79,27 @@ let context_cwd : Init_context.t Term.t =
7979
module Public_name = struct
8080
type t =
8181
| Use_name
82-
| Public_name of Dune_lang.Atom.t
82+
| Public_name of Public_name.t
8383

8484
let public_name_to_string = function
8585
| Use_name -> "<default>"
86-
| Public_name p -> Dune_lang.Atom.to_string p
86+
| Public_name p -> Public_name.to_string p
8787
;;
8888

8989
let public_name (common : Component.Options.Common.t) = function
9090
| None -> None
91-
| Some Use_name -> Some common.name
91+
| Some Use_name -> Some (Public_name.of_name_exn common.name)
9292
| Some (Public_name n) -> Some n
9393
;;
9494

9595
let conv =
96-
let parser = function
97-
| "" -> Ok Use_name
98-
| s -> component_name_parser s |> Result.map ~f:(fun a -> Public_name a)
96+
let parser s =
97+
if String.is_empty s
98+
then Ok Use_name
99+
else (
100+
match Public_name.of_string_user_error (Loc.none, s) with
101+
| Ok n -> Ok (Public_name n)
102+
| Error e -> Error (`Msg (User_message.to_string e)))
99103
in
100104
let printer ppf public_name =
101105
Format.pp_print_string ppf (public_name_to_string public_name)

init-public-name.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
- dune init: fix validation of `--public` argument (#...., fixes #7108, @emillon)

src/dune_lang/package_name.ml

Lines changed: 35 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -15,47 +15,50 @@ include (
1515
Dune_util.Stringlike with type t := t)
1616

1717
module Opam_compatible = struct
18-
include Dune_util.Stringlike.Make (struct
19-
type t = string
18+
let description_of_valid_string =
19+
Pp.text
20+
"Package names can contain letters, numbers, '-', '_' and '+', and need to contain \
21+
at least a letter."
22+
;;
2023

21-
let module_ = "Package.Name.Strict"
22-
let description = "opam package name"
23-
let to_string s = s
24+
module T = struct
25+
type t = string
26+
27+
let module_ = "Package.Name.Strict"
28+
let description = "opam package name"
29+
let to_string s = s
30+
let description_of_valid_string = Some description_of_valid_string
2431

25-
let description_of_valid_string =
26-
Some
27-
(Pp.textf
28-
"Package names can contain letters, numbers, '-', '_' and '+', and need to \
29-
contain at least a letter.")
30-
;;
32+
let is_letter = function
33+
| 'a' .. 'z' | 'A' .. 'Z' -> true
34+
| _ -> false
35+
;;
3136

32-
let is_letter = function
33-
| 'a' .. 'z' | 'A' .. 'Z' -> true
34-
| _ -> false
35-
;;
37+
let is_other_valid_char = function
38+
| '0' .. '9' | '-' | '+' | '_' -> true
39+
| _ -> false
40+
;;
3641

37-
let is_other_valid_char = function
38-
| '0' .. '9' | '-' | '+' | '_' -> true
39-
| _ -> false
40-
;;
42+
let is_valid_char c = is_letter c || is_other_valid_char c
4143

42-
let is_valid_char c = is_letter c || is_other_valid_char c
44+
let is_valid_string s =
45+
let all_chars_valid = String.for_all s ~f:is_valid_char in
46+
let has_one_letter = String.exists s ~f:is_letter in
47+
all_chars_valid && has_one_letter
48+
;;
4349

44-
let is_valid_string s =
45-
let all_chars_valid = String.for_all s ~f:is_valid_char in
46-
let has_one_letter = String.exists s ~f:is_letter in
47-
all_chars_valid && has_one_letter
48-
;;
50+
let of_string_opt s = Option.some_if (is_valid_string s) s
4951

50-
let of_string_opt s = Option.some_if (is_valid_string s) s
52+
let make_valid s =
53+
let replaced = String.map s ~f:(fun c -> if is_valid_char c then c else '_') in
54+
if is_valid_string replaced then replaced else "p" ^ replaced
55+
;;
5156

52-
let make_valid s =
53-
let replaced = String.map s ~f:(fun c -> if is_valid_char c then c else '_') in
54-
if is_valid_string replaced then replaced else "p" ^ replaced
55-
;;
57+
let hint_valid = Some make_valid
58+
end
5659

57-
let hint_valid = Some make_valid
58-
end)
60+
include Dune_util.Stringlike.Make (T)
5961

62+
let make_valid = T.make_valid
6063
let to_package_name s = s
6164
end

src/dune_lang/package_name.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,5 +20,7 @@ module Opam_compatible : sig
2020
type package_name
2121

2222
val to_package_name : t -> package_name
23+
val description_of_valid_string : _ Pp.t
24+
val make_valid : string -> string
2325
end
2426
with type package_name := t
Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,4 @@
11
#7108: foo-bar is a valid public name, we should accept it.
22

33
$ dune init lib foo_bar --public foo-bar
4-
dune: option '--public': invalid component name `foo-bar'
5-
Library names must be non-empty and composed only of the
6-
following
7-
characters: 'A'..'Z', 'a'..'z', '_' or '0'..'9'.
8-
Usage: dune init library [OPTION]… NAME [PATH]
9-
Try 'dune init library --help' or 'dune --help' for more information.
10-
[1]
4+
Success: initialized library component named foo_bar
Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
When a public name is implicit from the name, it should still be validated as a
2+
public name.
3+
4+
$ dune init lib 0 --public
5+
Error: "0" is an invalid opam package name.
6+
Package names can contain letters, numbers, '-', '_' and '+', and need to
7+
contain at least a letter.
8+
Hint: p0 would be a correct opam package name
9+
[1]
Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,4 @@
11
Sub-library names should be accepted:
22

33
$ dune init lib lib_s1_s2 --public lib.sub1.sub2
4-
dune: option '--public': invalid component name `lib.sub1.sub2'
5-
Library names must be non-empty and composed only of the
6-
following
7-
characters: 'A'..'Z', 'a'..'z', '_' or '0'..'9'.
8-
Usage: dune init library [OPTION]… NAME [PATH]
9-
Try 'dune init library --help' or 'dune --help' for more information.
10-
[1]
4+
Success: initialized library component named lib_s1_s2

test/blackbox-tests/test-cases/github3046.t

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -25,10 +25,15 @@ are given as parameters
2525
`dune init lib foo --public="some/invalid&name!"` returns an informative parsing error
2626

2727
$ dune init lib foo --public="some/invalid&name!"
28-
dune: option '--public': invalid component name `some/invalid&name!'
29-
Library names must be non-empty and composed only of the
30-
following
31-
characters: 'A'..'Z', 'a'..'z', '_' or '0'..'9'.
28+
dune: option '--public': "some/invalid&name!" is an invalid public
29+
name.
30+
Public names are composed of an opam package name and optional
31+
dot-separated
32+
string suffixes.
33+
Package names can contain letters, numbers, '-', '_' and '+', and need
34+
to
35+
contain at least a letter.
36+
Hint: some_invalid_name_ would be a correct public name
3237
Usage: dune init library [OPTION]… NAME [PATH]
3338
Try 'dune init library --help' or 'dune --help' for more information.
3439
[1]

0 commit comments

Comments
 (0)