Skip to content

Commit 3ea0bb3

Browse files
tatchirgrinberg
authored andcommitted
fix: URI handling
Handle uri's according to the spec ps-id: 5491F726-E719-4A48-ABEA-477B5ADD8121
1 parent 7032cc3 commit 3ea0bb3

File tree

10 files changed

+503
-68
lines changed

10 files changed

+503
-68
lines changed

CHANGES.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,8 @@
55
- Fix a bad interaction between inferred interfaces and promotion code actions
66
in watch mode (#753)
77

8+
- Fix URI parsing (#739 fixes #471 and #459)
9+
810
# 1.12.2
911

1012
## Fixes

dune-project

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ possible and does not make any assumptions about IO.
4848
(description "An LSP server for OCaml.")
4949
(depends
5050
yojson
51+
uri
5152
(re (>= 1.5.0))
5253
(ppx_yojson_conv_lib (>= "v0.14"))
5354
dune-rpc

lsp/src/dune

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
(library
44
(name lsp)
55
(public_name lsp)
6-
(libraries jsonrpc ppx_yojson_conv_lib dyn uutf yojson)
6+
(libraries jsonrpc ppx_yojson_conv_lib dyn uutf yojson uri)
77
(lint
88
(pps ppx_yojson_conv)))
99

lsp/src/import.ml

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,8 @@ module String = struct
1818

1919
let index = index_opt
2020

21+
let is_empty s = length s = 0
22+
2123
let rec check_prefix s ~prefix len i =
2224
i = len || (s.[i] = prefix.[i] && check_prefix s ~prefix len (i + 1))
2325

@@ -32,6 +34,9 @@ module String = struct
3234
let prefix_len = length prefix in
3335
len >= prefix_len && check_prefix s ~prefix prefix_len 0
3436

37+
let add_prefix_if_not_exists s ~prefix =
38+
if is_prefix s ~prefix then s else prefix ^ s
39+
3540
let next_occurrence ~pattern text from =
3641
let plen = String.length pattern in
3742
let last = String.length text - plen in

lsp/src/uri0.ml

Lines changed: 91 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -1,31 +1,109 @@
1+
(* This module is based on the [vscode-uri] implementation:
2+
https://github.com/microsoft/vscode-uri/blob/main/src/uri.ts. It only
3+
supports scheme, authority and path. Query, port and fragment are not
4+
implemented *)
5+
16
open Import
27

38
module Private = struct
49
let win32 = ref Sys.win32
510
end
611

712
type t = Uri_lexer.t =
8-
{ scheme : string option
13+
{ scheme : string
914
; authority : string
1015
; path : string
1116
}
1217

13-
let t_of_yojson json = Json.Conv.string_of_yojson json |> Uri_lexer.of_string
18+
let backslash_to_slash =
19+
String.map ~f:(function
20+
| '\\' -> '/'
21+
| c -> c)
22+
23+
let slash_to_backslash =
24+
String.map ~f:(function
25+
| '/' -> '\\'
26+
| c -> c)
27+
28+
let of_path path =
29+
let path = if !Private.win32 then backslash_to_slash path else path in
30+
Uri_lexer.of_path path
31+
32+
let to_path { path; authority; scheme } =
33+
let path =
34+
let len = String.length path in
35+
if len = 0 then "/"
36+
else
37+
let buff = Buffer.create 64 in
38+
(if (not (String.is_empty authority)) && len > 1 && scheme = "file" then (
39+
Buffer.add_string buff "//";
40+
Buffer.add_string buff authority;
41+
Buffer.add_string buff path)
42+
else if len < 3 then Buffer.add_string buff path
43+
else
44+
let c0 = path.[0] in
45+
let c1 = path.[1] in
46+
let c2 = path.[2] in
47+
if
48+
c0 = '/'
49+
&& ((c1 >= 'A' && c1 <= 'Z') || (c1 >= 'a' && c1 <= 'z'))
50+
&& c2 = ':'
51+
then (
52+
Buffer.add_char buff (Char.lowercase_ascii c1);
53+
Buffer.add_substring buff path 2 (String.length path - 2))
54+
else Buffer.add_string buff path);
55+
Buffer.contents buff
56+
in
57+
if !Private.win32 then slash_to_backslash path else path
58+
59+
let of_string = Uri_lexer.of_string
60+
61+
let encode ?(allow_slash = false) s =
62+
let allowed_chars = if allow_slash then "/" else "" in
63+
Uri.pct_encode ~component:(`Custom (`Generic, allowed_chars, "")) s
1464

1565
let to_string { scheme; authority; path } =
16-
let b = Buffer.create 64 in
17-
scheme
18-
|> Option.iter (fun s ->
19-
Buffer.add_string b s;
20-
Buffer.add_char b ':');
21-
Buffer.add_string b "//";
22-
Buffer.add_string b authority;
23-
if not (String.is_prefix path ~prefix:"/") then Buffer.add_char b '/';
24-
Buffer.add_string b path;
25-
Buffer.contents b
66+
let buff = Buffer.create 64 in
67+
68+
if not (String.is_empty scheme) then (
69+
Buffer.add_string buff scheme;
70+
Buffer.add_char buff ':');
71+
72+
if authority = "file" || scheme = "file" then Buffer.add_string buff "//";
73+
74+
(*TODO: implement full logic:
75+
https://github.com/microsoft/vscode-uri/blob/96acdc0be5f9d5f2640e1c1f6733bbf51ec95177/src/uri.ts#L605 *)
76+
(if not (String.is_empty authority) then
77+
let s = String.lowercase_ascii authority in
78+
Buffer.add_string buff (encode s));
79+
80+
(if not (String.is_empty path) then
81+
let encode = encode ~allow_slash:true in
82+
let encoded_colon = "%3A" in
83+
let len = String.length path in
84+
if len >= 3 && path.[0] = '/' && path.[2] = ':' then (
85+
let drive_letter = Char.lowercase_ascii path.[1] in
86+
if drive_letter >= 'a' && drive_letter <= 'z' then (
87+
Buffer.add_char buff '/';
88+
Buffer.add_char buff drive_letter;
89+
Buffer.add_string buff encoded_colon;
90+
let s = String.sub path ~pos:3 ~len:(len - 3) in
91+
Buffer.add_string buff (encode s)))
92+
else if len >= 2 && path.[1] = ':' then (
93+
let drive_letter = Char.lowercase_ascii path.[0] in
94+
if drive_letter >= 'a' && drive_letter <= 'z' then (
95+
Buffer.add_char buff drive_letter;
96+
Buffer.add_string buff encoded_colon;
97+
let s = String.sub path ~pos:2 ~len:(len - 2) in
98+
Buffer.add_string buff (encode s)))
99+
else Buffer.add_string buff (encode path));
100+
101+
Buffer.contents buff
26102

27103
let yojson_of_t t = `String (to_string t)
28104

105+
let t_of_yojson json = Json.Conv.string_of_yojson json |> of_string
106+
29107
let equal = ( = )
30108

31109
let compare (x : t) (y : t) = Stdlib.compare x y
@@ -35,23 +113,7 @@ let hash = Hashtbl.hash
35113
let to_dyn { scheme; authority; path } =
36114
let open Dyn in
37115
record
38-
[ ("scheme", (option string) scheme)
116+
[ ("scheme", string scheme)
39117
; ("authority", string authority)
40118
; ("path", string path)
41119
]
42-
43-
let to_path t =
44-
let path =
45-
t.path
46-
|> String.replace_all ~pattern:"\\" ~with_:"/"
47-
|> String.replace_all ~pattern:"%5C" ~with_:"/"
48-
|> String.replace_all ~pattern:"%3A" ~with_:":"
49-
|> String.replace_all ~pattern:"%20" ~with_:" "
50-
|> String.replace_all ~pattern:"%3D" ~with_:"="
51-
|> String.replace_all ~pattern:"%3F" ~with_:"?"
52-
in
53-
if !Private.win32 then path else Filename.concat "/" path
54-
55-
let of_path (path : string) =
56-
let path = Uri_lexer.escape_path path in
57-
{ path; scheme = Some "file"; authority = "" }

lsp/src/uri_lexer.mli

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,9 @@
11
type t =
2-
{ scheme : string option
2+
{ scheme : string
33
; authority : string
44
; path : string
55
}
66

77
val of_string : string -> t
88

9-
val escape_path : string -> string
9+
val of_path : string -> t

lsp/src/uri_lexer.mll

Lines changed: 31 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -1,38 +1,45 @@
11
{
22
type t =
3-
{ scheme : string option
3+
{ scheme : string
44
; authority : string
55
; path : string
66
}
77
}
88

9-
rule path = parse
10-
| '/'? { path1 (Buffer.create 12) lexbuf }
11-
and path1 buf = parse
12-
| '\\' { Buffer.add_char buf '/' ; path1 buf lexbuf }
13-
| "%5" ['c' 'C'] { Buffer.add_char buf '/' ; path1 buf lexbuf }
14-
| "%3" ['a' 'A'] { Buffer.add_char buf ':' ; path1 buf lexbuf }
15-
| "%3" ['d' 'D'] { Buffer.add_char buf '=' ; path1 buf lexbuf }
16-
| "%3" ['f' 'F'] { Buffer.add_char buf '?' ; path1 buf lexbuf }
17-
| "%20" { Buffer.add_char buf ' ' ; path1 buf lexbuf }
18-
| _ as c { Buffer.add_char buf c ; path1 buf lexbuf }
19-
| eof { Buffer.contents buf }
9+
rule uri = parse
10+
([^':''/''?''#']+ as scheme ':') ?
11+
("//" ([^'/''?''#']* as authority)) ?
12+
([^'?''#']* as path)
13+
{
14+
let open Import in
15+
let scheme = scheme |> Option.value ~default:"file" in
16+
let authority =
17+
authority |> Option.map Uri.pct_decode |> Option.value ~default:""
18+
in
19+
let path =
20+
let path = path |> Uri.pct_decode in
21+
match scheme with
22+
| "http" | "https" | "file" ->
23+
String.add_prefix_if_not_exists path ~prefix:"/"
24+
| _ -> path
25+
in
26+
{ scheme; authority; path; }
27+
}
2028

21-
and uri = parse
22-
| ([^ ':']+) as scheme ':' { uri1 (Some scheme) lexbuf }
23-
| "" { uri1 None lexbuf }
24-
and uri1 scheme = parse
25-
| "//" ([^ '/']* as authority) { uri2 scheme authority lexbuf }
26-
| "" { uri2 scheme "" lexbuf }
27-
and uri2 scheme authority = parse
28-
| "" { { scheme ; authority ; path = path lexbuf } }
29+
and path = parse
30+
| "" { { scheme = "file"; authority = ""; path = "/" } }
31+
| "//" ([^ '/']* as authority) (['/']_* as path) { { scheme = "file"; authority; path } }
32+
| "//" ([^ '/']* as authority) { { scheme = "file"; authority; path = "/" } }
33+
| ("/" _* as path) { { scheme = "file"; authority = ""; path } }
34+
| (_* as path) { { scheme = "file"; authority = ""; path = "/" ^ path } }
2935

30-
{
31-
let escape_path s =
32-
let lexbuf = Lexing.from_string s in
33-
path lexbuf
3436

37+
{
3538
let of_string s =
3639
let lexbuf = Lexing.from_string s in
3740
uri lexbuf
41+
42+
let of_path s =
43+
let lexbuf = Lexing.from_string s in
44+
path lexbuf
3845
}

0 commit comments

Comments
 (0)