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+
16open Import
27
38module Private = struct
49 let win32 = ref Sys. win32
510end
611
712type 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
1565let 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
27103let yojson_of_t t = `String (to_string t)
28104
105+ let t_of_yojson json = Json.Conv. string_of_yojson json |> of_string
106+
29107let equal = ( = )
30108
31109let compare (x : t ) (y : t ) = Stdlib. compare x y
@@ -35,23 +113,7 @@ let hash = Hashtbl.hash
35113let 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 = " " }
0 commit comments