Skip to content

Commit

Permalink
Merge 8a2dbec into 73678a6
Browse files Browse the repository at this point in the history
  • Loading branch information
rgrinberg committed Jun 8, 2023
2 parents 73678a6 + 8a2dbec commit 2a5571f
Show file tree
Hide file tree
Showing 5 changed files with 89 additions and 19 deletions.
18 changes: 15 additions & 3 deletions lsp/src/uri0.ml
Expand Up @@ -13,8 +13,11 @@ type t = Uri_lexer.t =
{ scheme : string
; authority : string
; path : string
; query : string option
}

let query t = t.query

let backslash_to_slash =
String.map ~f:(function
| '\\' -> '/'
Expand All @@ -29,7 +32,7 @@ let of_path path =
let path = if !Private.win32 then backslash_to_slash path else path in
Uri_lexer.of_path path

let to_path { path; authority; scheme } =
let to_path { path; authority; scheme; query } =
let path =
let len = String.length path in
if len = 0 then "/"
Expand All @@ -52,6 +55,11 @@ let to_path { path; authority; scheme } =
Buffer.add_char buff (Char.lowercase_ascii c1);
Buffer.add_substring buff path 2 (String.length path - 2))
else Buffer.add_string buff path);
(match query with
| None -> ()
| Some query ->
Buffer.add_char buff '?';
Buffer.add_string buff query);
Buffer.contents buff
in
if !Private.win32 then slash_to_backslash path else path
Expand Down Expand Up @@ -89,7 +97,7 @@ let encode ?(allow_slash = false) s =
scan 0 0;
Buffer.contents buf

let to_string { scheme; authority; path } =
let to_string { scheme; authority; path; query } =
let buff = Buffer.create 64 in

if not (String.is_empty scheme) then (
Expand Down Expand Up @@ -124,7 +132,11 @@ let to_string { scheme; authority; path } =
let s = String.sub path ~pos:2 ~len:(len - 2) in
Buffer.add_string buff (encode s)))
else Buffer.add_string buff (encode path));

(match query with
| None -> ()
| Some q ->
Buffer.add_char buff '?';
Buffer.add_string buff (encode q));
Buffer.contents buff

let yojson_of_t t = `String (to_string t)
Expand Down
2 changes: 2 additions & 0 deletions lsp/src/uri0.mli
Expand Up @@ -16,6 +16,8 @@ val of_path : string -> t

val to_string : t -> string

val query : t -> string option

module Private : sig
val win32 : bool ref
end
1 change: 1 addition & 0 deletions lsp/src/uri_lexer.mli
Expand Up @@ -2,6 +2,7 @@ type t =
{ scheme : string
; authority : string
; path : string
; query : string option
}

val of_string : string -> t
Expand Down
55 changes: 42 additions & 13 deletions lsp/src/uri_lexer.mll
@@ -1,8 +1,12 @@
{

open Import

type t =
{ scheme : string
; authority : string
; path : string
; query: string option
}

let int_of_hex_char c =
Expand All @@ -14,6 +18,15 @@ let int_of_hex_char c =
else
None

let value_exn = function
| None -> assert false
| Some s -> s

let char_of_hexdigits high low =
let high = value_exn (int_of_hex_char high) in
let low = value_exn (int_of_hex_char low) in
Char.chr (high lsl 4 + low)

(* https://github.com/mirage/ocaml-uri/blob/master/lib/uri.ml#L318 *)
let decode b =
let len = String.length b in
Expand Down Expand Up @@ -55,12 +68,24 @@ let decode b =
Buffer.contents buf
}

rule uri = parse
([^':''/''?''#']+ as scheme ':') ?
("//" ([^'/''?''#']* as authority)) ?
([^'?''#']* as path)
{
let open Import in
let hexdigit = ['a'-'f' 'A'-'F' '0'-'9']
let unreserved = [ 'A'-'Z' 'a'-'z' '0'-'9' '-' '.' '_' '~' ]
let sub_delim = [ '!' '$' '&' '\'' '(' ')' '*' '+' ';' '=' ]

rule query b = parse
| (['/' '?' ':' '@'] | unreserved | sub_delim) as c { Buffer.add_char b c; query b lexbuf }
| "%" (hexdigit as high) (hexdigit as low)
{ Buffer.add_char b (char_of_hexdigits high low);
query b lexbuf
}
| "" | "#" | eof { Buffer.contents b }

and uri = parse
([^':' '/' '?' '#']+ as scheme ':') ?
("//" ([^ '/' '?' '#']* as authority)) ?
([^ '?' '#']* as path)
(('?' ([^ '#']* as raw_query) '#'?)) ?
{
let scheme = scheme |> Option.value ~default:"file" in
let authority =
authority |> Option.map decode |> Option.value ~default:""
Expand All @@ -72,16 +97,20 @@ rule uri = parse
String.add_prefix_if_not_exists path ~prefix:"/"
| _ -> path
in
{ scheme; authority; path; }
let query =
match raw_query with
| None -> None
| Some c -> Some (query (Buffer.create (String.length c)) (Lexing.from_string c))
in
{ scheme; authority; path; query }
}

and path = parse
| "" { { scheme = "file"; authority = ""; path = "/" } }
| "//" ([^ '/']* as authority) (['/']_* as path) { { scheme = "file"; authority; path } }
| "//" ([^ '/']* as authority) { { scheme = "file"; authority; path = "/" } }
| ("/" _* as path) { { scheme = "file"; authority = ""; path } }
| (_* as path) { { scheme = "file"; authority = ""; path = "/" ^ path } }

| "" { { scheme = "file"; authority = ""; path = "/"; query = None } }
| "//" ([^ '/']* as authority) (['/']_* as path) { { scheme = "file"; authority; path ; query = None } }
| "//" ([^ '/']* as authority) { { scheme = "file"; authority; path = "/" ; query = None } }
| ("/" _* as path) { { scheme = "file"; authority = ""; path ; query = None } }
| (_* as path) { { scheme = "file"; authority = ""; path = "/" ^ path ; query = None } }

{
let of_string s =
Expand Down
32 changes: 29 additions & 3 deletions lsp/test/uri_tests.ml
Expand Up @@ -11,20 +11,46 @@ let run_with_modes 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)
Printf.printf "%s -> %s\n" s (Uri.to_path uri);
match Uri.query uri with
| None -> ()
| Some q -> Printf.printf "query: %s\n" q
in
fun uris -> run_with_modes (fun () -> List.iter test uris)

let%expect_test "test uri parsing" =
test_uri_parsing [ "file:///Users/foo"; "file:///c:/Users/foo" ];
test_uri_parsing
[ "file:///Users/foo"
; "file:///c:/Users/foo"
; "file:///foo?x=y"
; "http://xyz?foo#"
; "http://xxx?"
; "http://xyz?ab%3D1%23"
];
[%expect
{|
Unix:
file:///Users/foo -> /Users/foo
file:///c:/Users/foo -> c:/Users/foo
file:///foo?x=y -> /foo?x=y
query: x=y
http://xyz?foo# -> /?foo
query: foo
http://xxx? -> /?
query:
http://xyz?ab%3D1%23 -> /?ab=1#
query: ab=1#
Windows:
file:///Users/foo -> \Users\foo
file:///c:/Users/foo -> c:\Users\foo |}]
file:///c:/Users/foo -> c:\Users\foo
file:///foo?x=y -> \foo?x=y
query: x=y
http://xyz?foo# -> \?foo
query: foo
http://xxx? -> \?
query:
http://xyz?ab%3D1%23 -> \?ab=1#
query: ab=1# |}]

let uri_of_path =
let test path =
Expand Down

0 comments on commit 2a5571f

Please sign in to comment.