@@ -285,30 +285,38 @@ let rec nestable_block_element :
285285 (kind, { value = `Reference href; location = href_location }, content, m);
286286 location;
287287 } -> (
288+ let fallback error =
289+ Error. raise_warning error;
290+ let placeholder =
291+ match kind with
292+ | `Simple -> `Code_span href
293+ | `With_text -> `Styled (`Emphasis , content)
294+ in
295+ `Paragraph
296+ (inline_elements status [ placeholder |> Location. at location ])
297+ |> Location. at location
298+ in
288299 match Error. raise_warnings (Reference. parse href_location href) with
289- | Result. Ok target ->
300+ | Result. Ok target -> (
290301 let text = inline_elements status content in
291- let target =
292- match target with
293- | `Asset _ as a -> a
294- | `Root (_ , `TAsset) as a -> a
295- | `Root (s , `TUnknown) -> `Root (s, `TAsset )
296- | `Root _ -> failwith " a"
297- | `Dot (_ , s ) -> failwith s
298- | `Resolved _ -> failwith " todo2"
299- | _ -> failwith " todo"
300- in
301- `Media (`Reference target, m, text) |> Location. at location
302- | Result. Error error ->
303- Error. raise_warning error;
304- let placeholder =
305- match kind with
306- | `Simple -> `Code_span href
307- | `With_text -> `Styled (`Emphasis , content)
302+ let asset_ref_of_ref :
303+ Paths.Reference. t -> (Paths.Reference.Asset. t , _ ) result =
304+ function
305+ | `Asset _ as a -> Ok a
306+ | `Root (_ , `TAsset) as a -> Ok a
307+ | `Root (s , `TUnknown) -> Ok (`Root (s, `TAsset ))
308+ | `Dot (p , s ) -> Ok (`Dot (p, s))
309+ | _ ->
310+ Error
311+ (not_allowed ~suggestion: " Use a reference to an asset"
312+ href_location ~what: " Non-asset reference"
313+ ~in_what: " media target" )
308314 in
309- `Paragraph
310- (inline_elements status [ placeholder |> Location. at location ])
311- |> Location. at location)
315+ match asset_ref_of_ref target with
316+ | Error error -> fallback error
317+ | Ok target ->
318+ `Media (`Reference target, m, text) |> Location. at location)
319+ | Result. Error error -> fallback error)
312320
313321and nestable_block_elements status elements =
314322 List. map (nestable_block_element status) elements
0 commit comments