Skip to content

Commit

Permalink
test: enable uri tests on windows with hacks
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed Apr 17, 2022
1 parent 7aa21de commit 42ace2e
Show file tree
Hide file tree
Showing 3 changed files with 45 additions and 19 deletions.
6 changes: 5 additions & 1 deletion lsp/src/uri0.ml
Original file line number Diff line number Diff line change
@@ -1,5 +1,9 @@
open Import

module Private = struct
let win32 = ref Sys.win32
end

type t = Uri_lexer.t =
{ scheme : string option
; authority : string
Expand Down Expand Up @@ -46,7 +50,7 @@ let to_path t =
|> String.replace_all ~pattern:"%3D" ~with_:"="
|> String.replace_all ~pattern:"%3F" ~with_:"?"
in
if Sys.win32 then path else Filename.concat "/" path
if !Private.win32 then path else Filename.concat "/" path

let of_path (path : string) =
let path = Uri_lexer.escape_path path in
Expand Down
4 changes: 4 additions & 0 deletions lsp/src/uri0.mli
Original file line number Diff line number Diff line change
Expand Up @@ -17,3 +17,7 @@ val to_path : t -> string
val of_path : string -> t

val to_string : t -> string

module Private : sig
val win32 : bool ref
end
54 changes: 36 additions & 18 deletions lsp/test/uri_tests.ml
Original file line number Diff line number Diff line change
@@ -1,25 +1,43 @@
open Lsp

let run_with_modes f =
print_endline "Unix:";
Lsp.Uri.Private.win32 := false;
f ();
print_endline "Windows:";
Lsp.Uri.Private.win32 := true;
f ()

let test_uri_parsing =
let test s =
let uri = Uri.t_of_yojson (`String s) in
Printf.printf "%s -> %s\n" s (Uri.to_path uri)
in
fun uris -> run_with_modes (fun () -> List.iter test uris)

let%expect_test "test uri parsing" =
let uri = Uri.t_of_yojson (`String "file:///Users/foo") in
print_endline (Uri.to_path uri);
[%expect {|
/Users/foo |}];
print_endline (Uri.to_string uri);
[%expect {| file:///Users/foo |}];
let uri = Uri.t_of_yojson (`String "file:///c:/Users/foo") in
print_endline (Uri.to_path uri);
[%expect {| /c:/Users/foo |}];
print_endline (Uri.to_string uri);
test_uri_parsing [ "file:///Users/foo"; "file:///c:/Users/foo" ];
[%expect {|
file:///c:/Users/foo |}]
Unix:
file:///Users/foo -> /Users/foo
file:///c:/Users/foo -> /c:/Users/foo
Windows:
file:///Users/foo -> Users/foo
file:///c:/Users/foo -> c:/Users/foo |}]

let uri_of_path =
let test path =
let uri = Uri.of_path path in
Printf.printf "%s -> %s\n" path (Uri.to_string uri)
in
fun uris -> run_with_modes (fun () -> List.iter test uris)

let%expect_test "uri of path" =
let uri = Uri.of_path "/foo/bar.ml" in
print_endline (Uri.to_string uri);
[%expect {|
file:///foo/bar.ml |}];
let uri = Uri.of_path "foo/bar.mli" in
print_endline (Uri.to_string uri);
uri_of_path [ "/foo/bar.ml"; "foo/bar.mli" ];
[%expect {|
file:///foo/bar.mli |}]
Unix:
/foo/bar.ml -> file:///foo/bar.ml
foo/bar.mli -> file:///foo/bar.mli
Windows:
/foo/bar.ml -> file:///foo/bar.ml
foo/bar.mli -> file:///foo/bar.mli |}]

0 comments on commit 42ace2e

Please sign in to comment.