Skip to content

Commit

Permalink
refactor(uri): switch [of_path] to an ocamllex implementation
Browse files Browse the repository at this point in the history
  • Loading branch information
tatchi committed Jul 1, 2022
1 parent 9901eac commit 1ee25ea
Show file tree
Hide file tree
Showing 4 changed files with 27 additions and 24 deletions.
3 changes: 3 additions & 0 deletions lsp/src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,9 @@ module String = struct
let prefix_len = length prefix in
len >= prefix_len && check_prefix s ~prefix prefix_len 0

let add_prefix_if_not_exists s ~prefix =
if is_prefix s ~prefix then s else prefix ^ s

let next_occurrence ~pattern text from =
let plen = String.length pattern in
let last = String.length text - plen in
Expand Down
24 changes: 2 additions & 22 deletions lsp/src/uri0.ml
Original file line number Diff line number Diff line change
Expand Up @@ -25,30 +25,10 @@ let slash_to_backslash =
| '/' -> '\\'
| c -> c)

let add_prefix_if_not_exists s ~prefix =
if String.is_prefix s ~prefix then s else prefix ^ s

let of_path path =
let path = if !Private.win32 then backslash_to_slash path else path in
let path, authority =
let len = String.length path in
if len = 0 then ("/", "")
else if String.is_prefix path ~prefix:"//" then
let offset = 2 in
let idx = String.index_from_opt path offset '/' in
match idx with
| None -> ("/", String.sub path ~pos:offset ~len:(len - offset))
| Some i ->
let authority = String.sub path ~pos:offset ~len:(i - offset) in
let path =
let path = String.sub path ~pos:i ~len:(len - i) in
if String.is_empty path then "/" else path
in
(path, authority)
else (path, "")
in
let path = add_prefix_if_not_exists path ~prefix:"/" in
{ scheme = "file"; authority; path }
let Uri_lexer.{ scheme; authority; path } = Uri_lexer.of_path path in
{ scheme; authority; path }

let to_path { path; authority; scheme } =
let path =
Expand Down
2 changes: 2 additions & 0 deletions lsp/src/uri_lexer.mli
Original file line number Diff line number Diff line change
Expand Up @@ -5,3 +5,5 @@ type t =
}

val of_string : string -> t

val of_path : string -> t
22 changes: 20 additions & 2 deletions lsp/src/uri_lexer.mll
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ rule uri = parse
("//" ([^'/''?''#']* as authority)) ?
([^'?''#']* as path)
{
let open Import in
let scheme = scheme |> Option.value ~default:"file" in
let authority =
authority |> Option.map Uri.pct_decode |> Option.value ~default:""
Expand All @@ -19,14 +20,31 @@ rule uri = parse
let path = path |> Uri.pct_decode in
match scheme with
| "http" | "https" | "file" ->
if Import.String.is_prefix path ~prefix:"/" then path else "/" ^ path
String.add_prefix_if_not_exists path ~prefix:"/"
| _ -> path
in
{scheme ; authority; path;}
{ scheme; authority; path; }
}

and path = parse
| "" { { scheme = "file"; authority = ""; path = "/" } }
| "//" ([^ '/']* as authority) (['/']_* as path) { { scheme = "file"; authority; path } }
| "//" ([^ '/']* as authority) { { scheme = "file"; authority; path = "/" } }
| _* as path
{
let open Import in
{ scheme = "file"
; authority = ""
; path = String.add_prefix_if_not_exists path ~prefix:"/"
}
}

{
let of_string s =
let lexbuf = Lexing.from_string s in
uri lexbuf

let of_path s =
let lexbuf = Lexing.from_string s in
path lexbuf
}

0 comments on commit 1ee25ea

Please sign in to comment.