Skip to content

Commit

Permalink
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Fix copy# for Microsoft C compiler
Browse files Browse the repository at this point in the history
Microsoft CL doesn't support #n and requires the more strictly correct
directive #line

Signed-off-by: David Allsopp <[email protected]>
dra27 committed Dec 7, 2017

Partially verified

This commit is signed with the committer’s verified signature.
spydon’s contribution has been verified via GPG key.
We cannot verify signatures from co-authors, and some of the co-authors attributed to this commit require their commits to be signed.
1 parent 4bc5189 commit 6fd4d67
Showing 4 changed files with 19 additions and 1 deletion.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
@@ -14,6 +14,8 @@ next

- Build documentation for non public libraries (#306)

- Fix copy# for C/C++ with Microsoft C compiler (#353)

1.0+beta16 (05/11/2017)
-----------------------

8 changes: 7 additions & 1 deletion src/action.ml
Original file line number Diff line number Diff line change
@@ -596,7 +596,13 @@ let rec exec t ~ectx ~dir ~env_extra ~stdout_to ~stderr_to =
Io.with_file_in (Path.to_string src) ~f:(fun ic ->
Io.with_file_out (Path.to_string dst) ~f:(fun oc ->
let fn = Path.drop_build_context src in
Printf.fprintf oc "# 1 %S\n" (Path.to_string fn);
let directive =
if List.mem (Path.get_extension fn) [".c"; ".cpp"; ".h"] then
"line"
else
""
in
Printf.fprintf oc "#%s 1 %S\n" directive (Path.to_string fn);
Io.copy_channels ic oc));
return ()
| System cmd ->
8 changes: 8 additions & 0 deletions src/path.ml
Original file line number Diff line number Diff line change
@@ -425,4 +425,12 @@ let change_extension ~ext t =
let t = try Filename.chop_extension t with Not_found -> t in
t ^ ext

let get_extension t =
try
let t' = Filename.chop_extension t in
let l = String.length t' in
String.sub t l (String.length t - l)
with Not_found ->
""

let pp = Format.pp_print_string
2 changes: 2 additions & 0 deletions src/path.mli
Original file line number Diff line number Diff line change
@@ -112,4 +112,6 @@ val rm_rf : t -> unit
(** Changes the extension of the filename (or adds an extension if there was none) *)
val change_extension : ext:string -> t -> t

val get_extension : t -> string

val pp : t Fmt.t

0 comments on commit 6fd4d67

Please sign in to comment.