Skip to content

Commit

Permalink
Merge branch 'main' into top_fixes
Browse files Browse the repository at this point in the history
  • Loading branch information
nojb authored Feb 17, 2021
2 parents 06ebbc5 + ac6d7cd commit 2693a23
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 12 deletions.
25 changes: 19 additions & 6 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -86,14 +86,27 @@ let prefix_target common s = common.target_prefix ^ s

let instrument_with t = t.instrument_with

(* To avoid needless recompilations under Windows, where the case of
[Sys.getcwd] can vary between different invocations of [dune], normalize to
lowercase. *)
let normalize_path p =
(* To avoid needless recompilations under Windows, normalize the drive letter to
uppercase. *)
let normalize_path path =
if Sys.win32 then
Path.External.lowercase_ascii p
let src = Path.External.to_string path in
let is_letter = function
| 'a' .. 'z'
| 'A' .. 'Z' ->
true
| _ -> false
in
if String.length src >= 2 && is_letter src.[0] && src.[1] = ':' then (
let dst = Bytes.create (String.length src) in
Bytes.set dst 0 (Char.uppercase_ascii src.[0]);
Bytes.blit_string ~src ~src_pos:1 ~dst ~dst_pos:1
~len:(String.length src - 1);
Path.External.of_string (Bytes.unsafe_to_string dst)
) else
path
else
p
path

let set_dirs c =
if c.root.dir <> Filename.current_dir_name then Sys.chdir c.root.dir;
Expand Down
4 changes: 0 additions & 4 deletions src/stdune/path.ml
Original file line number Diff line number Diff line change
Expand Up @@ -50,8 +50,6 @@ module External : sig
val cwd : unit -> t

val as_local : t -> string

val lowercase_ascii : t -> t
end = struct
module T =
Interned.No_interning
Expand Down Expand Up @@ -166,8 +164,6 @@ end = struct
else
String.is_prefix ~prefix:(to_string a ^ "/") (to_string b)

let lowercase_ascii t = make (String.lowercase_ascii (to_string t))

module Set = struct
include T.Set

Expand Down
2 changes: 0 additions & 2 deletions src/stdune/path.mli
Original file line number Diff line number Diff line change
Expand Up @@ -111,8 +111,6 @@ module External : sig
val relative : t -> string -> t

val mkdir_p : ?perms:int -> t -> unit

val lowercase_ascii : t -> t
end

module Build : sig
Expand Down

0 comments on commit 2693a23

Please sign in to comment.