Skip to content

Commit

Permalink
fix syntax
Browse files Browse the repository at this point in the history
Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon committed Aug 3, 2023
1 parent 8b42dca commit 5701a53
Show file tree
Hide file tree
Showing 3 changed files with 43 additions and 30 deletions.
45 changes: 25 additions & 20 deletions src/dune_lang/package_name.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,35 +32,40 @@ module Strict = struct
let description_of_valid_string =
Some
(Pp.textf
"Package names start with a letter and can contain letters, \
numbers, '-', '_' and '+'")

let is_valid_char ~at_start = function
| 'a' .. 'z' | 'A' .. 'Z' -> true
| '0' .. '9' | '-' | '_' | '+' -> not at_start
| _ -> false
"Package names can contain letters '-', '_' and '+', and need to contain at least a letter.")

let of_string_opt s =
let open Option.O in
let* empty =
String.fold_left s ~init:(Some true) ~f:(fun state c ->
let* at_start = state in
if is_valid_char ~at_start c then Some false else None)
let* has_letter =
String.fold_left
~f:(fun acc c ->
match (acc, c) with
| None, _ -> None
| _, ('a' .. 'z' | 'A' .. 'Z') -> Some true
| _, ('0' .. '9' | '-' | '_' | '+') -> acc
| _ -> None)
~init:(Some false) s
in
Option.some_if (not empty) s
Option.some_if has_letter s

let make_valid s =
let b = Buffer.create 0 in
let emit c = Buffer.add_char b c in
let (_ : bool) =
String.fold_left s ~init:true ~f:(fun at_start c ->
if is_valid_char ~at_start c then emit c
else if not at_start then emit '_';
false)
let has_letter =
String.fold_left s ~init:false ~f:(fun acc c ->
match c with
| 'a' .. 'z' | 'A' .. 'Z' ->
emit c;
true
| '0' .. '9' | '-' | '_' | '+' ->
emit c;
acc
| _ ->
emit '_';
acc)
in
match Buffer.contents b with
| "" -> "a"
| s -> s
let s = Buffer.contents b in
if has_letter then s else "p" ^ s

let hint_valid = Some make_valid
end)
Expand Down
4 changes: 2 additions & 2 deletions src/dune_lang/package_name.mli
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ include Dune_sexp.Conv.S with type t := t
include Stringlike with type t := t

module Strict : sig
(** A variant that enforces opam package name constraints:
[[a-zA-Z][a-zA-Z0-9_+-]*] *)
(** A variant that enforces opam package name constraints: all characters are
[[a-zA-Z0-9_+-]] with at least a letter. *)

include Stringlike

Expand Down
24 changes: 16 additions & 8 deletions test/blackbox-tests/test-cases/package-name-strict.t
Original file line number Diff line number Diff line change
Expand Up @@ -33,14 +33,6 @@ Validation:
Leading invalid characters are removed:

$ test '0test'
File "dune-project", line 3, characters 7-12:
3 | (name 0test)
^^^^^
Error: "0test" is an invalid package name.
Package names start with a letter and can contain letters, numbers, '-', '_'
and '+'
Hint: test would be a correct package name
[1]

When all characters are removed, a valid name is suggested:

Expand All @@ -53,3 +45,19 @@ When all characters are removed, a valid name is suggested:
and '+'
Hint: a would be a correct package name
[1]

A package name can start with a number:

$ test 0install

But it needs at least a letter:

$ test 0-9
File "dune-project", line 3, characters 7-10:
3 | (name 0-9)
^^^
Error: "0-9" is an invalid package name.
Package names start with a letter and can contain letters, numbers, '-', '_'
and '+'
Hint: -9 would be a correct package name
[1]

0 comments on commit 5701a53

Please sign in to comment.