Skip to content

Commit 46a216e

Browse files
committed
Reintroduce emptyness check in path components
1 parent be725bc commit 46a216e

File tree

4 files changed

+59
-43
lines changed

4 files changed

+59
-43
lines changed

src/model/reference.ml

Lines changed: 54 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -126,7 +126,7 @@ type token = {
126126
location : Location_.span;
127127
}
128128

129-
type path_prefix = Path_prefix of string
129+
type path_prefix = Path_prefix of string * Location_.span
130130

131131
(* The string is scanned right-to-left, because we are interested in right-most
132132
hyphens. The tokens are also returned in right-to-left order, because the
@@ -205,7 +205,10 @@ let tokenize location s : token list * path_prefix option =
205205
let location = Location_.span [ location; identifier_location ] in
206206
(kind, location)
207207
and scan_path started_at tokens =
208-
(tokens, Some (Path_prefix (String.sub s 0 (started_at + 1))))
208+
let location =
209+
Location_.in_string s ~offset:0 ~length:(started_at + 1) location
210+
in
211+
(tokens, Some (Path_prefix (String.sub s 0 (started_at + 1), location)))
209212
in
210213

211214
scan_identifier (String.length s) 0 (String.length s - 1) []
@@ -219,15 +222,41 @@ let expected ?(expect_paths = false) allowed location =
219222
let allowed = List.map (Printf.sprintf "'%s-'") allowed @ unqualified in
220223
expected_err (pp_hum_comma_separated Format.pp_print_string) allowed location
221224

222-
let parse_path p =
225+
let parse_path whole_path_location p =
223226
let segs = String.split_on_char '/' p in
227+
let check segs start =
228+
let _finish =
229+
List.fold_left
230+
(fun offset seg ->
231+
match seg with
232+
| "" ->
233+
let location =
234+
Location_.in_string p ~offset ~length:0 whole_path_location
235+
in
236+
should_not_be_empty ~what:"Identifier in path reference" location
237+
|> Error.raise_exception
238+
| seg -> offset + String.length seg + 1)
239+
start segs
240+
in
241+
()
242+
in
224243
match segs with
225-
| "." :: segs -> (`TRelativePath, segs)
226-
| "" :: "" :: segs -> (`TCurrentPackage, segs)
227-
| "" :: segs -> (`TAbsolutePath, segs)
228-
| segs -> (`TRelativePath, segs)
229-
230-
let parse_path_prefix (Path_prefix p) identifier = parse_path (p ^ identifier)
244+
| "." :: segs ->
245+
check segs 2;
246+
(`TRelativePath, segs)
247+
| "" :: "" :: segs ->
248+
check segs 2;
249+
(`TCurrentPackage, segs)
250+
| "" :: segs ->
251+
check segs 1;
252+
(`TAbsolutePath, segs)
253+
| segs ->
254+
check segs 0;
255+
(`TRelativePath, segs)
256+
257+
let parse_path_prefix (Path_prefix (p, path_location)) identifier
258+
prefix_location =
259+
parse_path (Location_.span [ path_location; prefix_location ]) (p ^ identifier)
231260

232261
(* Parse references that do not contain a [/]. Raises errors and warnings. *)
233262
let parse whole_reference_location s :
@@ -253,7 +282,7 @@ let parse whole_reference_location s :
253282
| Some p -> (
254283
match kind with
255284
| `TUnknown | `TModule ->
256-
`Module_path (parse_path_prefix p identifier)
285+
`Module_path (parse_path_prefix p identifier location)
257286
| _ ->
258287
expected ~expect_paths:true [ "module" ] location
259288
|> Error.raise_exception))
@@ -285,7 +314,7 @@ let parse whole_reference_location s :
285314
| Some p -> (
286315
match kind with
287316
| `TUnknown | `TModule ->
288-
`Module_path (parse_path_prefix p identifier)
317+
`Module_path (parse_path_prefix p identifier location)
289318
| _ ->
290319
expected ~expect_paths:true [ "module" ] location
291320
|> Error.raise_exception))
@@ -333,20 +362,25 @@ let parse whole_reference_location s :
333362

334363
let label_parent_path kind path_prefix identifier location =
335364
match kind with
336-
| `TUnknown -> `Any_path (parse_path_prefix path_prefix identifier)
337-
| `TModule -> `Module_path (parse_path_prefix path_prefix identifier)
338-
| `TPage -> `Page_path (parse_path_prefix path_prefix identifier)
365+
| `TUnknown ->
366+
`Any_path (parse_path_prefix path_prefix identifier location)
367+
| `TModule ->
368+
`Module_path (parse_path_prefix path_prefix identifier location)
369+
| `TPage -> `Page_path (parse_path_prefix path_prefix identifier location)
339370
| _ ->
340371
expected ~expect_paths:true [ "module"; "page" ] location
341372
|> Error.raise_exception
342373
in
343374

344375
let any_path kind path_prefix identifier location =
345376
match kind with
346-
| `TUnknown -> `Any_path (parse_path_prefix path_prefix identifier)
347-
| `TModule -> `Module_path (parse_path_prefix path_prefix identifier)
348-
| `TPage -> `Page_path (parse_path_prefix path_prefix identifier)
349-
| `TAsset -> `Asset_path (parse_path_prefix path_prefix identifier)
377+
| `TUnknown ->
378+
`Any_path (parse_path_prefix path_prefix identifier location)
379+
| `TModule ->
380+
`Module_path (parse_path_prefix path_prefix identifier location)
381+
| `TPage -> `Page_path (parse_path_prefix path_prefix identifier location)
382+
| `TAsset ->
383+
`Asset_path (parse_path_prefix path_prefix identifier location)
350384
| _ ->
351385
expected ~expect_paths:true [ "module"; "page" ] location
352386
|> Error.raise_exception
@@ -532,9 +566,9 @@ let parse whole_reference_location s :
532566
|> Error.raise_exception)
533567

534568
(* Parse references that do not contain a [/]. Raises errors and warnings. *)
535-
let parse_asset (* whole_reference_location *) s :
569+
let parse_asset whole_reference_location s :
536570
Paths.Reference.Asset.t Error.with_errors_and_warnings =
537-
let path = parse_path s in
571+
let path = parse_path whole_reference_location s in
538572
Error.catch_errors_and_warnings (fun () -> `Asset_path path)
539573

540574
type path = [ `Root of string | `Dot of Paths.Path.Module.t * string ]

src/model/reference.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ val parse :
44
Location_.span -> string -> Paths.Reference.t Error.with_errors_and_warnings
55

66
val parse_asset :
7-
(* Location_.span -> *)
7+
Location_.span ->
88
string ->
99
Paths.Reference.Asset.t Error.with_errors_and_warnings
1010

src/model/semantics.ml

Lines changed: 2 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -282,7 +282,7 @@ let rec nestable_block_element :
282282
| {
283283
value =
284284
`Media
285-
(kind, { value = `Reference href; location = _href_location }, content, m);
285+
(kind, { value = `Reference href; location = href_location }, content, m);
286286
location;
287287
} -> (
288288
let fallback error =
@@ -296,27 +296,9 @@ let rec nestable_block_element :
296296
(inline_elements status [ placeholder |> Location.at location ])
297297
|> Location.at location
298298
in
299-
match
300-
Error.raise_warnings (Reference.parse_asset (* href_location *) href)
301-
with
299+
match Error.raise_warnings (Reference.parse_asset href_location href) with
302300
| Result.Ok target ->
303301
let text = inline_elements status content in
304-
(* let asset_ref_of_ref : *)
305-
(* Paths.Reference.t -> (Paths.Reference.Asset.t, _) Result.result = *)
306-
(* function *)
307-
(* | `Asset_path _ as a -> Result.Ok a *)
308-
(* (\* | `Root (_, `TAsset) as a -> Ok a *\) *)
309-
(* (\* | `Root (s, `TUnknown) -> Ok (`Root (s, `TAsset)) *\) *)
310-
(* (\* | `Dot (p, s) -> Ok (`Dot (p, s)) *\) *)
311-
(* | _ -> *)
312-
(* Error *)
313-
(* (not_allowed ~suggestion:"Use a reference to an asset" *)
314-
(* href_location ~what:"Non-asset reference" *)
315-
(* ~in_what:"media target") *)
316-
(* in *)
317-
(* match asset_ref_of_ref target with *)
318-
(* | Error error -> fallback error *)
319-
(* | Ok target -> *)
320302
`Media (`Reference target, m, text) |> Location.at location
321303
| Result.Error error -> fallback error)
322304

test/model/semantics/test.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2858,12 +2858,12 @@ let%expect_test _ =
28582858
let err_relative_empty_component =
28592859
test "{!foo//bar}";
28602860
[%expect
2861-
{| {"value":[{"`Paragraph":[{"`Reference":[{"`Any_path":["`TRelativePath",["foo","","bar"]]},[]]}]}],"warnings":[]} |}]
2861+
{| {"value":[{"`Paragraph":[{"`Code_span":"foo//bar"}]}],"warnings":["File \"f.ml\", line 1, characters 6-6:\nIdentifier in path reference should not be empty."]} |}]
28622862

28632863
let err_current_package_empty_component =
28642864
test "{!///bar}";
28652865
[%expect
2866-
{| {"value":[{"`Paragraph":[{"`Reference":[{"`Any_path":["`TCurrentPackage",["","bar"]]},[]]}]}],"warnings":[]} |}]
2866+
{| {"value":[{"`Paragraph":[{"`Code_span":"///bar"}]}],"warnings":["File \"f.ml\", line 1, characters 4-4:\nIdentifier in path reference should not be empty."]} |}]
28672867

28682868
let err_last_empty_component =
28692869
test "{!foo/}";

0 commit comments

Comments
 (0)