@@ -126,7 +126,7 @@ type token = {
126
126
location : Location_ .span ;
127
127
}
128
128
129
- type path_prefix = Path_prefix of string
129
+ type path_prefix = Path_prefix of string * Location_ .span
130
130
131
131
(* The string is scanned right-to-left, because we are interested in right-most
132
132
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 =
205
205
let location = Location_. span [ location; identifier_location ] in
206
206
(kind, location)
207
207
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)))
209
212
in
210
213
211
214
scan_identifier (String. length s) 0 (String. length s - 1 ) []
@@ -219,15 +222,41 @@ let expected ?(expect_paths = false) allowed location =
219
222
let allowed = List. map (Printf. sprintf " '%s-'" ) allowed @ unqualified in
220
223
expected_err (pp_hum_comma_separated Format. pp_print_string) allowed location
221
224
222
- let parse_path p =
225
+ let parse_path whole_path_location p =
223
226
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
224
243
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)
231
260
232
261
(* Parse references that do not contain a [/]. Raises errors and warnings. *)
233
262
let parse whole_reference_location s :
@@ -253,7 +282,7 @@ let parse whole_reference_location s :
253
282
| Some p -> (
254
283
match kind with
255
284
| `TUnknown | `TModule ->
256
- `Module_path (parse_path_prefix p identifier)
285
+ `Module_path (parse_path_prefix p identifier location )
257
286
| _ ->
258
287
expected ~expect_paths: true [ " module" ] location
259
288
|> Error. raise_exception))
@@ -285,7 +314,7 @@ let parse whole_reference_location s :
285
314
| Some p -> (
286
315
match kind with
287
316
| `TUnknown | `TModule ->
288
- `Module_path (parse_path_prefix p identifier)
317
+ `Module_path (parse_path_prefix p identifier location )
289
318
| _ ->
290
319
expected ~expect_paths: true [ " module" ] location
291
320
|> Error. raise_exception))
@@ -333,20 +362,25 @@ let parse whole_reference_location s :
333
362
334
363
let label_parent_path kind path_prefix identifier location =
335
364
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)
339
370
| _ ->
340
371
expected ~expect_paths: true [ " module" ; " page" ] location
341
372
|> Error. raise_exception
342
373
in
343
374
344
375
let any_path kind path_prefix identifier location =
345
376
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)
350
384
| _ ->
351
385
expected ~expect_paths: true [ " module" ; " page" ] location
352
386
|> Error. raise_exception
@@ -532,9 +566,9 @@ let parse whole_reference_location s :
532
566
|> Error. raise_exception)
533
567
534
568
(* 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 :
536
570
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
538
572
Error. catch_errors_and_warnings (fun () -> `Asset_path path)
539
573
540
574
type path = [ `Root of string | `Dot of Paths.Path.Module .t * string ]
0 commit comments