Skip to content

Commit

Permalink
feature: check package names are valid opam names
Browse files Browse the repository at this point in the history
This adds a `Package_name.Strict` variant that uses opam conventions.
The corresponding parser is used if lang dune >= 3.11.

Signed-off-by: Etienne Millon <[email protected]>
  • Loading branch information
emillon committed Aug 3, 2023
1 parent 69109f0 commit ee548a6
Show file tree
Hide file tree
Showing 6 changed files with 338 additions and 217 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,9 @@ Unreleased

- No longer emit linkopts(javascript) in META files (#8168, @hhugo)

- Ensure that package names in `dune-project` are valid opam package
names. (#...., @emillon)

3.10.0 (2023-07-31)
-------------------

Expand Down
53 changes: 50 additions & 3 deletions src/dune_lang/package_name.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,55 @@ include (

let hint_valid = None

let of_string_opt s =
(* DUNE3 verify no dots or spaces *)
if s = "" then None else Some s
let of_string_opt s = if s = "" then None else Some s
end) :
Dune_util.Stringlike with type t := t)

module Strict = struct
include Dune_util.Stringlike.Make (struct
type t = string

let module_ = "Package.Name.Strict"

let description = "package name"

let to_string s = s

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

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)
in
Option.some_if (not empty) 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)
in
match Buffer.contents b with
| "" -> "a"
| s -> s

let hint_valid = Some make_valid
end)

let to_package_name s = s
end
12 changes: 12 additions & 0 deletions src/dune_lang/package_name.mli
Original file line number Diff line number Diff line change
Expand Up @@ -14,3 +14,15 @@ include Comparable_intf.S with type key := t
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_+-]*] *)

include Stringlike

type package_name

val to_package_name : t -> package_name
end
with type package_name := t
Loading

0 comments on commit ee548a6

Please sign in to comment.