Skip to content

Commit

Permalink
Do not use regex to define default standard dirs
Browse files Browse the repository at this point in the history
Because regex does not work in bootstrap

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Nov 28, 2018
1 parent 9c0aa70 commit ac85ba5
Show file tree
Hide file tree
Showing 3 changed files with 9 additions and 10 deletions.
15 changes: 5 additions & 10 deletions src/file_tree.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,14 +9,9 @@ module Sub_dirs = struct

let default =
let standard_dirs =
let open Re in
[ empty
; seq [set "._"; rep any]
]
|> alt
|> Glob.of_re
|> Predicate_lang.of_glob
|> Predicate_lang.compl
Predicate_lang.of_pred (function
| "" -> false
| s -> s.[0] <> '.' && s.[0] <> '_')
in
{ sub_dirs = standard_dirs
; data_only = Predicate_lang.empty
Expand All @@ -28,7 +23,7 @@ module Sub_dirs = struct
let sub_dirs = Option.value sub_dirs ~default:default.sub_dirs in
Predicate_lang.diff sub_dirs ignored_sub_dirs
in
let data_only = Option.value data_only ~default:default.sub_dirs in
let data_only = Option.value data_only ~default:default.data_only in
{ sub_dirs ; data_only }

let ignore_dirs t ~dirs =
Expand Down Expand Up @@ -343,7 +338,7 @@ let load ?(extra_ignored_subtrees=Path.Set.empty) path =
| Ignored -> (false, data_only)
| Data_only -> (true, true)
in
if is_subdir then
if not is_subdir then
acc
else
let dirs_visited =
Expand Down
2 changes: 2 additions & 0 deletions src/predicate_lang.ml
Original file line number Diff line number Diff line change
Expand Up @@ -109,6 +109,8 @@ let union t = Ast.Union t

let of_glob g = Ast.Element (Glob.test g)

let of_pred p = Ast.Element p

let of_string_set s = Ast.Element (String.Set.mem s)

let compl t = Ast.Compl t
Expand Down
2 changes: 2 additions & 0 deletions src/predicate_lang.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,8 @@ val filter : t -> standard:t -> string list -> string list

val of_glob : Glob.t -> t

val of_pred : (string -> bool) -> t

val compl : t -> t

val union : t list -> t
Expand Down

0 comments on commit ac85ba5

Please sign in to comment.