Skip to content

Commit

Permalink
[stdune] add String.filter_map
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
Signed-off-by: Ulysse Gérard <thevoodoos@gmail.com>
  • Loading branch information
rgrinberg authored and voodoos committed Aug 5, 2020
1 parent 1a307bf commit b8a43f0
Show file tree
Hide file tree
Showing 4 changed files with 24 additions and 23 deletions.
20 changes: 9 additions & 11 deletions src/dune/lib_name.ml
Original file line number Diff line number Diff line change
Expand Up @@ -31,17 +31,15 @@ module Local = struct
let hint_valid =
Some
(fun name ->
String.to_seq name
|> Seq.filter_map ~f:(fun c ->
if valid_char c then
Some c
else
match c with
| '.'
| '-' ->
Some '_'
| _ -> None)
|> String.of_seq)
String.filter_map name ~f:(fun c ->
if valid_char c then
Some c
else
match c with
| '.'
| '-' ->
Some '_'
| _ -> None))

let of_string_opt (name : string) =
match name with
Expand Down
21 changes: 9 additions & 12 deletions src/dune/module_name.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,18 +28,15 @@ include Stringlike.Make (struct
let hint_valid =
Some
(fun name ->
String.to_seq name
|> Seq.filter_map ~f:(fun c ->
if valid_char c then
Some c
else
match c with
| '.'
| '-' ->
Some '_'
| _ -> None
)
|> String.of_seq)
String.filter_map name ~f:(fun c ->
if valid_char c then
Some c
else
match c with
| '.'
| '-' ->
Some '_'
| _ -> None))

let is_valid_module_name name =
match name with
Expand Down
4 changes: 4 additions & 0 deletions src/stdune/string.ml
Original file line number Diff line number Diff line change
Expand Up @@ -305,3 +305,7 @@ let of_list chars =
let s = Bytes.make (List.length chars) '0' in
List.iteri chars ~f:(fun i c -> Bytes.set s i c);
Bytes.to_string s

let filter_map t ~f =
(* TODO more efficient implementation *)
to_seq t |> Seq.filter_map ~f |> of_seq
2 changes: 2 additions & 0 deletions src/stdune/string.mli
Original file line number Diff line number Diff line change
Expand Up @@ -128,3 +128,5 @@ val need_quoting : string -> bool
(** [quote_for_shell s] quotes [s] using [Filename.quote] if [need_quoting s] is
[true] *)
val quote_for_shell : string -> string

val filter_map : string -> f:(char -> char option) -> string

0 comments on commit b8a43f0

Please sign in to comment.