diff options
-rw-r--r-- | ocamlbuild/configuration.ml | 24 | ||||
-rw-r--r-- | ocamlbuild/lexers.mli | 4 | ||||
-rw-r--r-- | ocamlbuild/lexers.mll | 11 |
3 files changed, 23 insertions, 16 deletions
diff --git a/ocamlbuild/configuration.ml b/ocamlbuild/configuration.ml index b2a596238..fad57bce0 100644 --- a/ocamlbuild/configuration.ml +++ b/ocamlbuild/configuration.ml @@ -19,9 +19,8 @@ open Lexers type t = Lexers.conf let acknowledge_config config = - List.iter - (fun (_, config) -> List.iter Param_tags.acknowledge config.plus_tags) - config + let ack (tag, _loc) = Param_tags.acknowledge tag in + List.iter (fun (_, config) -> List.iter ack config.plus_tags) config let cache = Hashtbl.create 107 let (configs, add_config) = @@ -33,23 +32,27 @@ let (configs, add_config) = Hashtbl.clear cache) let parse_lexbuf ?dir source lexbuf = - lexbuf.Lexing.lex_curr_p <- { lexbuf.Lexing.lex_curr_p with Lexing.pos_fname = source }; + lexbuf.Lexing.lex_curr_p <- + { lexbuf.Lexing.lex_curr_p with Lexing.pos_fname = source }; let conf = Lexers.conf_lines dir lexbuf in add_config conf -let parse_string s = parse_lexbuf (Printf.sprintf "String %S" s) (Lexing.from_string s) +let parse_string s = + parse_lexbuf (Printf.sprintf "STRING(%s)" s) (Lexing.from_string s) let parse_file ?dir file = with_input_file file begin fun ic -> - parse_lexbuf ?dir (Printf.sprintf "File %S" file) (Lexing.from_channel ic) + parse_lexbuf ?dir file (Lexing.from_channel ic) end let key_match = Glob.eval let apply_config s (config : t) init = + let add (tag, _loc) = Tags.add tag in + let remove (tag, _loc) = Tags.remove tag in List.fold_left begin fun tags (key, v) -> if key_match key s then - List.fold_right Tags.add v.plus_tags (List.fold_right Tags.remove v.minus_tags tags) + List.fold_right add v.plus_tags (List.fold_right remove v.minus_tags tags) else tags end init config @@ -72,11 +75,12 @@ let tag_any tags = if tags <> [] then parse_string (Printf.sprintf "true: %s" (String.concat ", " tags));; let check_tags_usage useful_tags = - let check_tag tag = + let check_tag (tag, loc) = if not (Tags.mem tag useful_tags) then - Log.eprintf "Warning: the tag %S used in your configuration \ + Log.eprintf "%aWarning: the tag %S used in your configuration \ is not mentioned in any rule and will have no effect. \ - It may be a typo." tag + It may be a typo." + Loc.print_loc loc tag in let check_conf (_, values) = List.iter check_tag values.plus_tags; diff --git a/ocamlbuild/lexers.mli b/ocamlbuild/lexers.mli index ae4939aa4..aa7dd5ada 100644 --- a/ocamlbuild/lexers.mli +++ b/ocamlbuild/lexers.mli @@ -15,8 +15,8 @@ exception Error of (string * Lexing.position) type conf_values = - { plus_tags : string list; - minus_tags : string list } + { plus_tags : (string * Loc.location) list; + minus_tags : (string * Loc.location) list } type conf = (Glob.globber * conf_values) list diff --git a/ocamlbuild/lexers.mll b/ocamlbuild/lexers.mll index 12099febd..35af2c34a 100644 --- a/ocamlbuild/lexers.mll +++ b/ocamlbuild/lexers.mll @@ -20,12 +20,15 @@ let error lexbuf fmt = Printf.ksprintf (fun s -> raise (Error (s,Lexing.lexeme_s open Glob_ast type conf_values = - { plus_tags : string list; - minus_tags : string list } + { plus_tags : (string * Loc.location) list; + minus_tags : (string * Loc.location) list } type conf = (Glob.globber * conf_values) list let empty = { plus_tags = []; minus_tags = [] } + +let locate lexbuf txt = + (txt, Loc.of_lexbuf lexbuf) } let newline = ('\n' | '\r' | "\r\n") @@ -122,8 +125,8 @@ and conf_lines dir = parse | _ { error lexbuf "Invalid line syntax" } and conf_value x = parse - | '-' (tag as tag) { { (x) with minus_tags = tag :: x.minus_tags } } - | '+'? (tag as tag) { { (x) with plus_tags = tag :: x.plus_tags } } + | '-' (tag as tag) { { (x) with minus_tags = locate lexbuf tag :: x.minus_tags } } + | '+'? (tag as tag) { { (x) with plus_tags = locate lexbuf tag :: x.plus_tags } } | (_ | eof) { error lexbuf "Invalid tag modifier only '+ or '-' are allowed as prefix for tag" } and conf_values x = parse |