@@ -76,8 +76,6 @@ module Path = struct
7676
7777 type t = { kind : string ; parent : t option ; name : string }
7878
79- let last t = t.name
80-
8179 let mk ?parent kind name = { kind; parent; name }
8280
8381 let rec from_identifier : source -> t = function
@@ -270,98 +268,12 @@ type t = Anchor.t
270268
271269let from_path page = { Anchor. page; anchor = " " ; kind = page.kind }
272270
273- let page x = x.Anchor. page
274-
275271let from_identifier ~stop_before = function
276272 | #Path. source as p when not stop_before ->
277273 Ok (from_path @@ Path. from_identifier p)
278274 | p -> Anchor. from_identifier p
279275
280- let from_identifier_exn ~stop_before id =
281- match from_identifier ~stop_before id with
282- | Error e -> failwith (Error. to_string e)
283- | Ok url -> url
284-
285276let kind id =
286277 match Anchor. from_identifier id with
287278 | Error e -> failwith (Error. to_string e)
288279 | Ok { kind; _ } -> kind
289-
290- (* module Of_path = struct
291- * let rec to_html : stop_before:bool -> Path.t -> _ =
292- * fun ~stop_before path ->
293- * match path with
294- * | `Root root -> [ Html.txt root ]
295- * | `Forward root -> [ Html.txt root ] (\* FIXME *\)
296- * | `Dot (prefix, suffix) ->
297- * let link = to_html ~stop_before:true (prefix :> Path.t) in
298- * link @ [ Html.txt ("." ^ suffix) ]
299- * | `Apply (p1, p2) ->
300- * let link1 = to_html ~stop_before (p1 :> Path.t) in
301- * let link2 = to_html ~stop_before (p2 :> Path.t) in
302- * link1 @ Html.txt "(":: link2 @ [ Html.txt ")" ]
303- * | `Resolved rp ->
304- * let id = Path.Resolved.identifier rp in
305- * let txt = Url.render_path path in
306- * begin match Id.href ~stop_before id with
307- * | href -> [ Html.a ~a:[ Html.a_href href ] [ Html.txt txt ] ]
308- * | exception Id.Not_linkable -> [ Html.txt txt ]
309- * | exception exn ->
310- * Printf.eprintf "Id.href failed: %S\n%!" (Printexc.to_string exn);
311- * [ Html.txt txt ]
312- * end
313- * end *)
314-
315- (* module Of_fragment = struct
316- * let dot prefix suffix =
317- * match prefix with
318- * | "" -> suffix
319- * | _ -> prefix ^ "." ^ suffix
320- *
321- * let rec render_raw : Fragment.t -> string =
322- * fun fragment ->
323- * match fragment with
324- * | `Resolved rr -> render_resolved rr
325- * | `Dot (prefix, suffix) -> dot (render_raw (prefix :> Fragment.t)) suffix
326- *
327- * and render_resolved : Fragment.Resolved.t -> string =
328- * let open Fragment.Resolved in
329- * fun fragment ->
330- * match fragment with
331- * | `Root -> ""
332- * | `Subst (_, rr) -> render_resolved (rr :> t)
333- * | `SubstAlias (_, rr) -> render_resolved (rr :> t)
334- * | `Module (rr, s) -> dot (render_resolved (rr :> t)) (ModuleName.to_string s)
335- * | `Type (rr, s) -> dot (render_resolved (rr :> t)) (TypeName.to_string s)
336- * | `Class (rr, s) -> dot (render_resolved ( rr :> t)) (ClassName.to_string s)
337- * | `ClassType (rr, s) -> dot (render_resolved (rr :> t)) (ClassTypeName.to_string s)
338- *
339- * let rec to_html : stop_before:bool ->
340- * Identifier.Signature.t -> Fragment.t -> _ =
341- * fun ~stop_before id fragment ->
342- * let open Fragment in
343- * match fragment with
344- * | `Resolved `Root ->
345- * begin match Id.href ~stop_before:true (id :> Identifier.t) with
346- * | href ->
347- * [Html.a ~a:[Html.a_href href] [Html.txt (Identifier.name id)]]
348- * | exception Id.Not_linkable -> [ Html.txt (Identifier.name id) ]
349- * | exception exn ->
350- * Printf.eprintf "[FRAG] Id.href failed: %S\n%!" (Printexc.to_string exn);
351- * [ Html.txt (Identifier.name id) ]
352- * end
353- * | `Resolved rr ->
354- * let id = Resolved.identifier id (rr :> Resolved.t) in
355- * let txt = render_resolved rr in
356- * begin match Id.href ~stop_before id with
357- * | href ->
358- * [ Html.a ~a:[ Html.a_href href ] [ Html.txt txt ] ]
359- * | exception Id.Not_linkable -> [ Html.txt txt ]
360- * | exception exn ->
361- * Printf.eprintf "[FRAG] Id.href failed: %S\n%!" (Printexc.to_string exn);
362- * [ Html.txt txt ]
363- * end
364- * | `Dot (prefix, suffix) ->
365- * let link = to_html ~stop_before:true id (prefix :> Fragment.t) in
366- * link @ [ Html.txt ("." ^ suffix) ]
367- * end *)
0 commit comments