Skip to content

Commit cf468f0

Browse files
panglesdjonludlam
authored andcommitted
Use Odoc_document.Url.Anchor to generate anchors in source code
The anchors are different, since source code anchors needs the full path, but at least the qualification is similar. Replaces `full_name` which did not included enough information to disambiguate functor parameters. Signed-off-by: Paul-Elliot <[email protected]>
1 parent fc051e8 commit cf468f0

File tree

12 files changed

+201
-171
lines changed

12 files changed

+201
-171
lines changed

src/document/url.ml

Lines changed: 1 addition & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -3,15 +3,6 @@ open Odoc_model.Paths
33
open Odoc_model.Names
44
module Root = Odoc_model.Root
55

6-
let functor_arg_pos : Odoc_model.Paths.Identifier.FunctorParameter.t -> int =
7-
let open Odoc_model.Paths.Identifier in
8-
fun { iv = `Parameter (p, _); _ } ->
9-
let rec inner_sig = function
10-
| `Result { iv = p; _ } -> 1 + inner_sig p
11-
| `Module _ | `ModuleType _ | `Root _ | `Parameter _ -> 1
12-
in
13-
inner_sig p.iv
14-
156
let render_path : Odoc_model.Paths.Path.t -> string =
167
let open Odoc_model.Paths.Path in
178
let rec render_resolved : Odoc_model.Paths.Path.Resolved.t -> string =
@@ -160,7 +151,7 @@ module Path = struct
160151
mk ~parent kind name
161152
| { iv = `Parameter (functor_id, arg_name); _ } as p ->
162153
let parent = from_identifier (functor_id :> any) in
163-
let arg_num = functor_arg_pos p in
154+
let arg_num = Identifier.FunctorParameter.functor_arg_pos p in
164155
let kind = `Parameter arg_num in
165156
let name = ModuleName.to_string arg_name in
166157
mk ~parent kind name

src/loader/dune

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -22,4 +22,4 @@
2222
(preprocess
2323
(action
2424
(run %{bin:cppo} -V OCAML:%{ocaml_version} %{input-file})))
25-
(libraries odoc_model odoc-parser syntax_highlighter))
25+
(libraries odoc_model odoc-parser syntax_highlighter odoc_document))

src/loader/implementation.ml

Lines changed: 72 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -381,37 +381,79 @@ let postprocess_poses source_id poses uid_to_id uid_to_loc =
381381
in
382382
defs @ poses
383383

384-
let string_of_full_name_ty : Odoc_model.Paths.Identifier.full_name_ty -> string
385-
= function
386-
| `Page -> "page"
387-
| `Module -> "module"
388-
| `Constructor -> "constructor"
389-
| `Field -> "field"
390-
| `Extension -> "extension"
391-
| `Exception -> "exception"
392-
| `Value -> "value"
393-
| `Class -> "class"
394-
| `ClassType -> "class_type"
395-
| `Method -> "method"
396-
| `InstanceVariable -> "instance_variable"
397-
| `Label -> "label"
398-
| `ModuleType -> "module_type"
399-
| `Type -> "type"
400-
| `Parameter -> "parameter"
401-
| `Src -> "src"
402-
| `Asset -> "asset"
403-
404384
let anchor_of_identifier id =
405-
let full_name = Odoc_model.Paths.Identifier.full_name id in
406-
List.filter_map
407-
(fun (x, y) ->
408-
match x with
409-
| `Page -> None
410-
| `Src -> None
411-
| `Asset -> None
412-
| _ -> Some (Printf.sprintf "%s-%s" (string_of_full_name_ty x) y))
413-
full_name
414-
|> List.tl |> String.concat "."
385+
let open Odoc_document.Url in
386+
let open Odoc_model.Paths in
387+
let open Odoc_model.Names in
388+
let rec anchor_of_identifier acc (id : Identifier.t) =
389+
let continue anchor parent =
390+
anchor_of_identifier (anchor :: acc) (parent :> Identifier.t)
391+
in
392+
let anchor kind name =
393+
Printf.sprintf "%s-%s" (Anchor.string_of_kind kind) name
394+
in
395+
match id.iv with
396+
| `InstanceVariable (parent, name) ->
397+
let anchor = anchor `Val (InstanceVariableName.to_string name) in
398+
continue anchor parent
399+
| `Parameter (parent, name) as iv ->
400+
let arg_num =
401+
Identifier.FunctorParameter.functor_arg_pos { id with iv }
402+
in
403+
let kind = `Parameter arg_num in
404+
let anchor = anchor kind (ModuleName.to_string name) in
405+
continue anchor parent
406+
| `Module (parent, name) ->
407+
let anchor = anchor `Module (ModuleName.to_string name) in
408+
continue anchor parent
409+
| `SourceDir _ -> assert false
410+
| `ModuleType (parent, name) ->
411+
let anchor = anchor `ModuleType (ModuleTypeName.to_string name) in
412+
continue anchor parent
413+
| `Method (parent, name) ->
414+
let anchor = anchor `Method (MethodName.to_string name) in
415+
continue anchor parent
416+
| `AssetFile _ -> assert false
417+
| `Field (parent, name) ->
418+
let anchor = anchor `Field (FieldName.to_string name) in
419+
continue anchor parent
420+
| `SourceLocationMod _ -> assert false
421+
| `Result parent -> anchor_of_identifier acc (parent :> Identifier.t)
422+
| `SourceLocationInt _ -> assert false
423+
| `Type (parent, name) ->
424+
let anchor = anchor `Type (TypeName.to_string name) in
425+
continue anchor parent
426+
| `Label _ -> assert false
427+
| `Exception (parent, name) ->
428+
let anchor = anchor `Exception (ExceptionName.to_string name) in
429+
continue anchor parent
430+
| `Class (parent, name) ->
431+
let anchor = anchor `Class (ClassName.to_string name) in
432+
continue anchor parent
433+
| `Page _ -> assert false
434+
| `LeafPage _ -> assert false
435+
| `CoreType _ -> assert false
436+
| `SourceLocation _ -> assert false
437+
| `ClassType (parent, name) ->
438+
let anchor = anchor `ClassType (ClassTypeName.to_string name) in
439+
continue anchor parent
440+
| `SourcePage _ -> assert false
441+
| `Value (parent, name) ->
442+
let anchor = anchor `Val (ValueName.to_string name) in
443+
continue anchor parent
444+
| `CoreException _ -> assert false
445+
| `Constructor (parent, name) ->
446+
let anchor = anchor `Constructor (ConstructorName.to_string name) in
447+
continue anchor parent
448+
| `Root _ ->
449+
(* We do not need to include the "container" root module in the anchor
450+
to have unique anchors. *)
451+
acc
452+
| `Extension (parent, name) ->
453+
let anchor = anchor `Extension (ExtensionName.to_string name) in
454+
continue anchor parent
455+
in
456+
anchor_of_identifier [] id |> String.concat "."
415457

416458
let of_cmt (source_id_opt : Odoc_model.Paths.Identifier.SourcePage.t option)
417459
(id : Odoc_model.Paths.Identifier.RootModule.t) (cmt : Cmt_format.cmt_infos)

src/model/paths.ml

Lines changed: 7 additions & 73 deletions
Original file line numberDiff line numberDiff line change
@@ -64,79 +64,6 @@ module Identifier = struct
6464

6565
let name : [< t_pv ] id -> string = fun n -> name_aux (n :> t)
6666

67-
type full_name_ty =
68-
[ `Page
69-
| `Module
70-
| `Parameter
71-
| `ModuleType
72-
| `Type
73-
| `Constructor
74-
| `Field
75-
| `Extension
76-
| `Exception
77-
| `Value
78-
| `Class
79-
| `ClassType
80-
| `Method
81-
| `InstanceVariable
82-
| `Label
83-
| `Src
84-
| `Asset ]
85-
let rec full_name_aux : t -> (full_name_ty * string) list =
86-
fun x ->
87-
match x.iv with
88-
| `Root (_, name) -> [ (`Module, ModuleName.to_string name) ]
89-
| `Page (_, name) -> [ (`Page, PageName.to_string name) ]
90-
| `LeafPage (_, name) -> [ (`Page, PageName.to_string name) ]
91-
| `Module (parent, name) ->
92-
(`Module, ModuleName.to_string name) :: full_name_aux (parent :> t)
93-
| `Parameter (parent, name) ->
94-
(`Parameter, ModuleName.to_string name) :: full_name_aux (parent :> t)
95-
| `Result x -> full_name_aux (x :> t)
96-
| `ModuleType (parent, name) ->
97-
(`ModuleType, ModuleTypeName.to_string name)
98-
:: full_name_aux (parent :> t)
99-
| `Type (parent, name) ->
100-
(`Type, TypeName.to_string name) :: full_name_aux (parent :> t)
101-
| `CoreType name -> [ (`Type, TypeName.to_string name) ]
102-
| `Constructor (parent, name) ->
103-
(`Constructor, ConstructorName.to_string name)
104-
:: full_name_aux (parent :> t)
105-
| `Field (parent, name) ->
106-
(`Field, FieldName.to_string name) :: full_name_aux (parent :> t)
107-
| `Extension (parent, name) ->
108-
(`Extension, ExtensionName.to_string name)
109-
:: full_name_aux (parent :> t)
110-
| `Exception (parent, name) ->
111-
(`Exception, ExceptionName.to_string name)
112-
:: full_name_aux (parent :> t)
113-
| `CoreException name -> [ (`Exception, ExceptionName.to_string name) ]
114-
| `Value (parent, name) ->
115-
(`Value, ValueName.to_string name) :: full_name_aux (parent :> t)
116-
| `Class (parent, name) ->
117-
(`Class, ClassName.to_string name) :: full_name_aux (parent :> t)
118-
| `ClassType (parent, name) ->
119-
(`ClassType, ClassTypeName.to_string name)
120-
:: full_name_aux (parent :> t)
121-
| `Method (parent, name) ->
122-
(`Method, MethodName.to_string name) :: full_name_aux (parent :> t)
123-
| `InstanceVariable (parent, name) ->
124-
(`InstanceVariable, InstanceVariableName.to_string name)
125-
:: full_name_aux (parent :> t)
126-
| `Label (parent, name) ->
127-
(`Label, LabelName.to_string name) :: full_name_aux (parent :> t)
128-
| `SourceDir (parent, name) -> (`Page, name) :: full_name_aux (parent :> t)
129-
| `SourceLocation (parent, name) ->
130-
(`Src, DefName.to_string name) :: full_name_aux (parent :> t)
131-
| `SourceLocationInt (parent, name) ->
132-
(`Src, LocalName.to_string name) :: full_name_aux (parent :> t)
133-
| `SourceLocationMod name -> full_name_aux (name :> t)
134-
| `SourcePage (parent, name) -> (`Page, name) :: full_name_aux (parent :> t)
135-
| `AssetFile (parent, name) -> (`Asset, name) :: full_name_aux (parent :> t)
136-
137-
let full_name : [< t_pv ] id -> (full_name_ty * string) list =
138-
fun n -> List.rev @@ full_name_aux (n :> t)
139-
14067
let rec label_parent_aux =
14168
let open Id in
14269
fun (n : non_src) ->
@@ -246,6 +173,13 @@ module Identifier = struct
246173
let equal = equal
247174
let hash = hash
248175
let compare = compare
176+
177+
let functor_arg_pos { iv = `Parameter (p, _); _ } =
178+
let rec inner_sig = function
179+
| `Result { iv = p; _ } -> 1 + inner_sig p
180+
| `Module _ | `ModuleType _ | `Root _ | `Parameter _ -> 1
181+
in
182+
inner_sig p.iv
249183
end
250184

251185
module FunctorResult = struct

src/model/paths.mli

Lines changed: 11 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -50,10 +50,17 @@ module Identifier : sig
5050

5151
module Module : IdSig with type t = Id.module_ and type t_pv = Id.module_pv
5252

53-
module FunctorParameter :
54-
IdSig
55-
with type t = Id.functor_parameter
56-
and type t_pv = Id.functor_parameter_pv
53+
module FunctorParameter : sig
54+
include
55+
IdSig
56+
with type t = Id.functor_parameter
57+
and type t_pv = Id.functor_parameter_pv
58+
59+
val functor_arg_pos : t -> int
60+
(** Gets the index in which the functor argument is, in the argument list.
61+
Useful to turn identifiers into unique anchors, since multiple arguments
62+
can have the same name. *)
63+
end
5764

5865
module ModuleType :
5966
IdSig with type t = Id.module_type and type t_pv = Id.module_type_pv
@@ -179,27 +186,6 @@ module Identifier : sig
179186

180187
val name : [< t_pv ] id -> string
181188

182-
type full_name_ty =
183-
[ `Page
184-
| `Module
185-
| `Parameter
186-
| `ModuleType
187-
| `Type
188-
| `Constructor
189-
| `Field
190-
| `Extension
191-
| `Exception
192-
| `Value
193-
| `Class
194-
| `ClassType
195-
| `Method
196-
| `InstanceVariable
197-
| `Label
198-
| `Src
199-
| `Asset ]
200-
201-
val full_name : [< t_pv ] id -> (full_name_ty * string) list
202-
203189
(* val root : [< t_pv ] id -> RootModule.t_pv id option *)
204190

205191
val compare : t -> t -> int

test/sources/double_wrapped.t/run.t

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ Look if all the source files are generated:
5858
<div class="odoc-spec">
5959
<div class="spec value anchored" id="val-x">
6060
<a href="#val-x" class="anchor"></a>
61-
<a href="../../root/source/a.ml.html#value-x" class="source_link">Source
61+
<a href="../../root/source/a.ml.html#val-x" class="source_link">Source
6262
</a><code><span><span class="keyword">val</span> x : int</span></code>
6363
</div>
6464
</div>

test/sources/functor.t/run.t

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -53,9 +53,9 @@ In this test, the functor expansion contains the right link.
5353
class="source_link">Source
5454
</a>
5555
--
56-
<a href="../../root/source/a.ml.html#module-F.value-y"
57-
class="source_link">Source
58-
</a>
56+
<a href="#val-y" class="anchor"></a>
57+
<a href="../../root/source/a.ml.html#module-F.val-y" class="source_link">
58+
Source
5959

6060
$ cat html/root/source/a.ml.html | grep L3
6161
<a id="L3" class="source_line" href="#L3">3</a>
@@ -75,11 +75,11 @@ However, on functor results, there is a link to source in the file:
7575
</a>
7676
<code><span><span class="keyword">type</span> t</span>
7777
--
78+
<div class="spec value anchored" id="val-y">
7879
<a href="#val-y" class="anchor"></a>
79-
<a href="../../root/source/a.ml.html#module-F.value-y"
80-
class="source_link">Source
80+
<a href="../../root/source/a.ml.html#module-F.val-y" class="source_link">
81+
Source
8182
</a>
82-
<code>
8383

8484
Source links in functor parameters might not make sense. Currently we generate none:
8585

test/sources/include_in_expansion.t/run.t

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,9 +28,9 @@ source parent of value y should be left to B.
2828
</h1>
2929
--
3030
<a href="#val-y" class="anchor"></a>
31-
<a href="../../root/source/b.ml.html#value-y" class="source_link">
32-
Source
31+
<a href="../../root/source/b.ml.html#val-y" class="source_link">Source
32+
</a><code><span><span class="keyword">val</span> y : int</span></code>
3333
--
3434
<a href="#val-x" class="anchor"></a>
35-
<a href="../../root/source/a.ml.html#value-x" class="source_link">Source
35+
<a href="../../root/source/a.ml.html#val-x" class="source_link">Source
3636
</a><code><span><span class="keyword">val</span> x : int</span></code>

test/sources/lookup_def.t/run.t

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -14,14 +14,14 @@ Show the locations:
1414
$ odoc_print a.odocl | jq -c '.. | select(.locs?) | [ .id, .locs ]'
1515
[{"`Module":[{"`Root":["None","A"]},"M"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-M"]}}]
1616
[{"`Module":[{"`Root":["None","A"]},"N"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-N"]}}]
17-
[{"`ModuleType":[{"`Module":[{"`Root":["None","A"]},"N"]},"S"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-N.module_type-S"]}}]
18-
[{"`Value":[{"`ModuleType":[{"`Module":[{"`Root":["None","A"]},"N"]},"S"]},"x"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-N.module_type-S"]}}]
17+
[{"`ModuleType":[{"`Module":[{"`Root":["None","A"]},"N"]},"S"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-N.module-type-S"]}}]
18+
[{"`Value":[{"`ModuleType":[{"`Module":[{"`Root":["None","A"]},"N"]},"S"]},"x"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-N.module-type-S"]}}]
1919
[{"`Module":[{"`Module":[{"`Root":["None","A"]},"N"]},"T"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-N.module-T"]}}]
20-
[{"`Value":[{"`Module":[{"`Module":[{"`Root":["None","A"]},"N"]},"T"]},"x"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-N.module-T.value-x"]}}]
20+
[{"`Value":[{"`Module":[{"`Module":[{"`Root":["None","A"]},"N"]},"T"]},"x"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"module-N.module-T.val-x"]}}]
2121
[{"`Type":[{"`Root":["None","A"]},"t"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"type-t"]}}]
22-
[{"`Value":[{"`Root":["None","A"]},"a"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"value-a"]}}]
22+
[{"`Value":[{"`Root":["None","A"]},"a"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"val-a"]}}]
2323
[{"`Exception":[{"`Root":["None","A"]},"Exn"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"exception-Exn"]}}]
2424
[{"`Type":[{"`Root":["None","A"]},"ext"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"type-ext"]}}]
2525
[{"`Extension":[{"`Root":["None","A"]},"Ext"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"extension-Ext"]}}]
2626
[{"`Class":[{"`Root":["None","A"]},"cls"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"class-cls"]}}]
27-
[{"`ClassType":[{"`Root":["None","A"]},"clst"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"class_type-clst"]}}]
27+
[{"`ClassType":[{"`Root":["None","A"]},"clst"]},{"Some":{"`SourceLocation":[{"`SourcePage":[{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]},"a.ml"]},"class-type-clst"]}}]

test/sources/lookup_def_wrapped.t/run.t

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ Look if all the source files are generated:
6262
<div class="odoc-spec">
6363
<div class="spec value anchored" id="val-x">
6464
<a href="#val-x" class="anchor"></a>
65-
<a href="../../root/source/a.ml.html#value-x" class="source_link">Source
65+
<a href="../../root/source/a.ml.html#val-x" class="source_link">Source
6666
</a><code><span><span class="keyword">val</span> x : int</span></code>
6767
</div>
6868
</div>

0 commit comments

Comments
 (0)