Skip to content

Commit

Permalink
Add warning for .cxx pre 1.8
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Feb 13, 2019
1 parent ec784e7 commit 5bd3f63
Show file tree
Hide file tree
Showing 3 changed files with 24 additions and 8 deletions.
15 changes: 10 additions & 5 deletions src/c.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,16 +10,21 @@ module Kind = struct
| C -> Format.pp_print_string fmt "c"
| Cxx -> Format.pp_print_string fmt "cpp"

type split =
| Unrecognized
| Not_allowed_until of Syntax.Version.t
| Recognized of string * t

let split_extension fn ~dune_version =
match String.lsplit2 fn ~on:'.' with
| Some (obj, "c") -> Some (obj, C)
| Some (obj, "cpp") -> Some (obj, Cxx)
| Some (obj, "c") -> Recognized (obj, C)
| Some (obj, "cpp") -> Recognized (obj, Cxx)
| Some (obj, "cxx") ->
if dune_version >= (1, 8) then
Some (obj, Cxx)
Recognized (obj, Cxx)
else
None
| _ -> None
Not_allowed_until (1, 8)
| _ -> Unrecognized

let possible_fns t fn ~dune_version =
match t with
Expand Down
7 changes: 6 additions & 1 deletion src/c.mli
Original file line number Diff line number Diff line change
Expand Up @@ -7,10 +7,15 @@ module Kind : sig

val pp : t Fmt.t

type split =
| Unrecognized
| Not_allowed_until of Syntax.Version.t
| Recognized of string * t

val split_extension
: string
-> dune_version:Syntax.Version.t
-> (string * t) option
-> split

(** [possible_fns t s] returns the possible filenames given the extension-less
basenames [s] *)
Expand Down
10 changes: 8 additions & 2 deletions src/c_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -49,8 +49,14 @@ let load_sources ~dune_version ~dir ~files =
let init = C.Kind.Dict.make String.Map.empty in
String.Set.fold files ~init ~f:(fun fn acc ->
match C.Kind.split_extension fn ~dune_version with
| None -> acc
| Some (obj, kind) ->
| Unrecognized -> acc
| Not_allowed_until version ->
let loc = Loc.in_dir dir in
Errors.warn loc
"Source file %s with extension %s is not allowed before version %a"
fn (Filename.extension fn) Syntax.Version.pp version;
acc
| Recognized (obj, kind) ->
let path = Path.relative dir fn in
C.Kind.Dict.update acc kind ~f:(fun v ->
String.Map.add v obj (C.Source.make ~kind ~path)
Expand Down

0 comments on commit 5bd3f63

Please sign in to comment.