Skip to content

Commit

Permalink
Use Comment.elements in document and index
Browse files Browse the repository at this point in the history
  • Loading branch information
Julow authored and panglesd committed Dec 13, 2024
1 parent 345ef53 commit 998b787
Show file tree
Hide file tree
Showing 12 changed files with 51 additions and 58 deletions.
4 changes: 2 additions & 2 deletions src/document/comment.ml
Original file line number Diff line number Diff line change
Expand Up @@ -413,8 +413,8 @@ let standalone docs =
Utils.flatmap ~f:item_element
@@ List.map (fun x -> x.Odoc_model.Location_.value) docs

let to_ir (docs : Comment.docs) =
let to_ir (docs : Comment.elements) =
Utils.flatmap ~f:block_element
@@ List.map (fun x -> x.Odoc_model.Location_.value) docs.elements
@@ List.map (fun x -> x.Odoc_model.Location_.value) docs

let has_doc docs = docs <> []
38 changes: 18 additions & 20 deletions src/document/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -530,10 +530,9 @@ module Make (Syntax : SYNTAX) = struct
field fld.mutable_ (fld.id :> Paths.Identifier.t) fld.type_
in
let anchor = Some url in
let rhs = Comment.to_ir fld.doc in
let doc =
if not (Comment.has_doc fld.doc.elements) then [] else rhs
in
let doc = fld.doc.elements in
let rhs = Comment.to_ir doc in
let doc = if not (Comment.has_doc doc) then [] else rhs in
let markers = Syntax.Comment.markers in
DocumentedSrc.Documented { anchor; attrs; code; doc; markers })
in
Expand Down Expand Up @@ -610,10 +609,9 @@ module Make (Syntax : SYNTAX) = struct
cstr.args cstr.res
in
let anchor = Some url in
let rhs = Comment.to_ir cstr.doc in
let doc =
if not (Comment.has_doc cstr.doc.elements) then [] else rhs
in
let doc = cstr.doc.elements in
let rhs = Comment.to_ir doc in
let doc = if not (Comment.has_doc doc) then [] else rhs in
let markers = Syntax.Comment.markers in
DocumentedSrc.Nested { anchor; attrs; code; doc; markers })
in
Expand All @@ -625,7 +623,7 @@ module Make (Syntax : SYNTAX) = struct
let anchor = Some url in
let attrs = [ "def"; "variant"; Url.Anchor.string_of_kind url.kind ] in
let code = O.documentedSrc (O.txt "| ") @ constructor id t.args t.res in
let doc = Comment.to_ir t.doc in
let doc = Comment.to_ir t.doc.elements in
let markers = Syntax.Comment.markers in
DocumentedSrc.Nested { anchor; attrs; code; doc; markers }

Expand All @@ -646,7 +644,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "type"; "extension" ] in
let anchor = Some (Url.Anchor.extension_decl t) in
let doc = Comment.to_ir t.doc in
let doc = Comment.to_ir t.doc.elements in
let source_anchor =
(* Take the anchor from the first constructor only for consistency with
regular variants. *)
Expand All @@ -666,7 +664,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "exception" ] in
let anchor = path_to_id t.id in
let doc = Comment.to_ir t.doc in
let doc = Comment.to_ir t.doc.elements in
let source_anchor = source_anchor t.source_loc in
Item.Declaration { attr; anchor; doc; content; source_anchor }

Expand Down Expand Up @@ -710,7 +708,7 @@ module Make (Syntax : SYNTAX) = struct
else O.txt " " ++ O.keyword "of" ++ O.sp ++ params)),
match doc with
| { elements = []; _ } -> None
| _ -> Some (Comment.to_ir doc) ))
| _ -> Some (Comment.to_ir doc.elements) ))
in
let markers = Syntax.Comment.markers in
try
Expand Down Expand Up @@ -881,7 +879,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = "type" :: (if is_substitution then [ "subst" ] else []) in
let anchor = path_to_id t.id in
let doc = Comment.to_ir t.doc in
let doc = Comment.to_ir t.doc.elements in
let source_anchor = source_anchor t.source_loc in
Item.Declaration { attr; anchor; doc; content; source_anchor }
end
Expand Down Expand Up @@ -909,7 +907,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "value" ] @ extra_attr in
let anchor = path_to_id t.id in
let doc = Comment.to_ir t.doc in
let doc = Comment.to_ir t.doc.elements in
let source_anchor = source_anchor t.source_loc in
Item.Declaration { attr; anchor; doc; content; source_anchor }
end
Expand Down Expand Up @@ -1010,7 +1008,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "method" ] in
let anchor = path_to_id t.id in
let doc = Comment.to_ir t.doc in
let doc = Comment.to_ir t.doc.elements in
Item.Declaration { attr; anchor; doc; content; source_anchor = None }

let instance_variable (t : Odoc_model.Lang.InstanceVariable.t) =
Expand All @@ -1029,7 +1027,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "value"; "instance-variable" ] in
let anchor = path_to_id t.id in
let doc = Comment.to_ir t.doc in
let doc = Comment.to_ir t.doc.elements in
Item.Declaration { attr; anchor; doc; content; source_anchor = None }

let inherit_ (ih : Lang.ClassSignature.Inherit.t) =
Expand All @@ -1043,7 +1041,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "inherit" ] in
let anchor = None in
let doc = Comment.to_ir ih.doc in
let doc = Comment.to_ir ih.doc.elements in
Item.Declaration { attr; anchor; doc; content; source_anchor = None }

let constraint_ (cst : Lang.ClassSignature.Constraint.t) =
Expand All @@ -1052,7 +1050,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [] in
let anchor = None in
let doc = Comment.to_ir cst.doc in
let doc = Comment.to_ir cst.doc.elements in
Item.Declaration { attr; anchor; doc; content; source_anchor = None }

let class_signature (c : Lang.ClassSignature.t) =
Expand Down Expand Up @@ -1314,7 +1312,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "module-substitution" ] in
let anchor = path_to_id t.id in
let doc = Comment.to_ir t.doc in
let doc = Comment.to_ir t.doc.elements in
Item.Declaration { attr; anchor; doc; content; source_anchor = None }

and module_type_substitution (t : Odoc_model.Lang.ModuleTypeSubstitution.t)
Expand Down Expand Up @@ -1724,7 +1722,7 @@ module Make (Syntax : SYNTAX) = struct
synopsis because no page is generated to render it and we'd loose
the full documentation.
The documentation from the expansion is not used. *)
Comment.to_ir t.doc
Comment.to_ir t.doc.elements
in
Item.Include { attr; anchor; doc; content; source_anchor = None }
end
Expand Down
2 changes: 1 addition & 1 deletion src/document/sidebar.ml
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,7 @@ end = struct
| Page { short_title = None; _ } ->
let title =
let open Odoc_model in
match Comment.find_zero_heading entry.doc.elements with
match Comment.find_zero_heading entry.doc with
| Some t -> t
| None ->
let name =
Expand Down
2 changes: 1 addition & 1 deletion src/index/entry.ml
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ type kind =

type t = {
id : Odoc_model.Paths.Identifier.Any.t;
doc : Odoc_model.Comment.docs;
doc : Odoc_model.Comment.elements;
kind : kind;
}

Expand Down
4 changes: 2 additions & 2 deletions src/index/entry.mli
Original file line number Diff line number Diff line change
Expand Up @@ -60,12 +60,12 @@ type kind =

type t = {
id : Odoc_model.Paths.Identifier.Any.t;
doc : Odoc_model.Comment.docs;
doc : Odoc_model.Comment.elements;
kind : kind;
}

val entry :
id:[< Odoc_model.Paths.Identifier.Any.t_pv ] Odoc_model.Paths.Identifier.id ->
doc:Odoc_model.Comment.docs ->
doc:Odoc_model.Comment.elements ->
kind:kind ->
t
32 changes: 16 additions & 16 deletions src/index/skeleton.ml
Original file line number Diff line number Diff line change
Expand Up @@ -6,21 +6,20 @@ open Odoc_utils
type t = Entry.t Tree.t

module Entry = struct
open Odoc_model.Comment

let of_comp_unit (u : Compilation_unit.t) =
let has_expansion = true in
let doc =
match u.content with
| Pack _ ->
{ Odoc_model.Comment.elements = []; suppress_warnings = false }
| Module m -> m.doc
match u.content with Pack _ -> [] | Module m -> m.doc.elements
in
Entry.entry ~id:u.id ~doc ~kind:(Module { has_expansion })

let of_module (m : Module.t) =
let has_expansion =
match m.type_ with Alias (_, None) -> false | _ -> true
in
Entry.entry ~id:m.id ~doc:m.doc ~kind:(Module { has_expansion })
Entry.entry ~id:m.id ~doc:m.doc.elements ~kind:(Module { has_expansion })

let of_module_type (mt : ModuleType.t) =
let has_expansion =
Expand All @@ -35,7 +34,8 @@ module Entry = struct
| _ -> false)
| _ -> true
in
Entry.entry ~id:mt.id ~doc:mt.doc ~kind:(ModuleType { has_expansion })
Entry.entry ~id:mt.id ~doc:mt.doc.elements
~kind:(ModuleType { has_expansion })

let of_type_decl (td : TypeDecl.t) =
let kind =
Expand All @@ -46,7 +46,7 @@ module Entry = struct
representation = td.representation;
}
in
Entry.entry ~id:td.id ~doc:td.doc ~kind
Entry.entry ~id:td.id ~doc:td.doc.elements ~kind

let varify_params =
List.mapi (fun i param ->
Expand All @@ -67,7 +67,7 @@ module Entry = struct
params )
in
let kind = Entry.Constructor { args; res } in
Entry.entry ~id:c.id ~doc:c.doc ~kind
Entry.entry ~id:c.id ~doc:c.doc.elements ~kind

let of_field id_parent params (field : TypeDecl.Field.t) =
let params = varify_params params in
Expand All @@ -81,7 +81,7 @@ module Entry = struct
Entry.Field
{ mutable_ = field.mutable_; type_ = field.type_; parent_type }
in
Entry.entry ~id:field.id ~doc:field.doc ~kind
Entry.entry ~id:field.id ~doc:field.doc.elements ~kind

let of_exception (exc : Exception.t) =
let res =
Expand All @@ -93,11 +93,11 @@ module Entry = struct
| Some x -> x
in
let kind = Entry.Exception { args = exc.args; res } in
Entry.entry ~id:exc.id ~doc:exc.doc ~kind
Entry.entry ~id:exc.id ~doc:exc.doc.elements ~kind

let of_value (v : Value.t) =
let kind = Entry.Value { value = v.value; type_ = v.type_ } in
Entry.entry ~id:v.id ~doc:v.doc ~kind
Entry.entry ~id:v.id ~doc:v.doc.elements ~kind

let of_extension_constructor type_path params (v : Extension.Constructor.t) =
let res =
Expand All @@ -108,26 +108,26 @@ module Entry = struct
TypeExpr.Constr (type_path, params)
in
let kind = Entry.ExtensionConstructor { args = v.args; res } in
Entry.entry ~id:v.id ~doc:v.doc ~kind
Entry.entry ~id:v.id ~doc:v.doc.elements ~kind

let of_class (cl : Class.t) =
let kind = Entry.Class { virtual_ = cl.virtual_; params = cl.params } in
Entry.entry ~id:cl.id ~doc:cl.doc ~kind
Entry.entry ~id:cl.id ~doc:cl.doc.elements ~kind

let of_class_type (ct : ClassType.t) =
let kind =
Entry.Class_type { virtual_ = ct.virtual_; params = ct.params }
in
Entry.entry ~id:ct.id ~doc:ct.doc ~kind
Entry.entry ~id:ct.id ~doc:ct.doc.elements ~kind

let of_method (m : Method.t) =
let kind =
Entry.Method
{ virtual_ = m.virtual_; private_ = m.private_; type_ = m.type_ }
in
Entry.entry ~id:m.id ~doc:m.doc ~kind
Entry.entry ~id:m.id ~doc:m.doc.elements ~kind

let of_docs id doc = Entry.entry ~id ~doc ~kind:Doc
let of_docs id doc = Entry.entry ~id ~doc:doc.elements ~kind:Doc
end

let if_non_hidden id f =
Expand Down
13 changes: 4 additions & 9 deletions src/index/skeleton_of.ml
Original file line number Diff line number Diff line change
Expand Up @@ -39,18 +39,15 @@ let compare_entry (t1 : t) (t2 : t) =
try_ Astring.String.compare by_name @@ fun () -> 0

let rec t_of_in_progress (dir : In_progress.in_progress) : t =
let empty_doc = { Comment.elements = []; suppress_warnings = false } in

let entry_of_page page =
let kind = Entry.Page page.Lang.Page.frontmatter in
let doc = page.content in
let doc = page.content.elements in
let id = page.name in
Entry.entry ~kind ~doc ~id
in
let entry_of_impl id =
let kind = Entry.Impl in
let doc = empty_doc in
Entry.entry ~kind ~doc ~id
Entry.entry ~kind ~doc:[] ~id
in
let children_order, index =
match In_progress.index dir with
Expand All @@ -63,16 +60,14 @@ let rec t_of_in_progress (dir : In_progress.in_progress) : t =
match In_progress.root_dir dir with
| Some id ->
let kind = Entry.Dir in
let doc = empty_doc in
Entry.entry ~kind ~doc ~id
Entry.entry ~kind ~doc:[] ~id
| None ->
let id =
(* root dir must have an index page *)
Id.Mk.leaf_page (None, Names.PageName.make_std "index")
in
let kind = Entry.Dir in
let doc = empty_doc in
Entry.entry ~kind ~doc ~id
Entry.entry ~kind ~doc:[] ~id
in
(None, entry)
in
Expand Down
2 changes: 1 addition & 1 deletion src/odoc/html_fragment.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input =
Odoc_xref2.Link.resolve_page ~filename:input_s env page
|> Odoc_model.Error.handle_warnings ~warnings_options
>>= fun resolved ->
let page = Odoc_document.Comment.to_ir resolved.content in
let page = Odoc_document.Comment.to_ir resolved.content.elements in
let config =
Odoc_html.Config.v ~semantic_uris:false ~indent:false ~flat:false
~open_details:false ~as_json:false ~remap:[] ()
Expand Down
4 changes: 2 additions & 2 deletions src/search/html.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,11 +27,11 @@ val names_of_id : Paths.Identifier.t -> string * string
The tuple is intended to be given respectively to the [prefix_name] and
[name] arguments of {!Odoc_html_frontend.of_strings}. *)

val of_doc : Comment.docs -> html
val of_doc : Comment.elements -> html
(** [of_doc d] returns the HTML associated of the documentation comment [d],
generated correctly for search (no links or anchors). *)

val html_string_of_doc : Comment.docs -> string
val html_string_of_doc : Comment.elements -> string
(** [html_string_of_doc d] is the same as {!of_doc} converted to a
string. *)

Expand Down
2 changes: 1 addition & 1 deletion src/search/json_index/json_search.ml
Original file line number Diff line number Diff line change
Expand Up @@ -81,7 +81,7 @@ let rec of_id x =

let of_id n = `Array (List.rev @@ of_id (n :> Odoc_model.Paths.Identifier.t))

let of_doc (doc : Odoc_model.Comment.docs) =
let of_doc (doc : Odoc_model.Comment.elements) =
let txt = Text.of_doc doc in
`String txt

Expand Down
4 changes: 2 additions & 2 deletions src/search/text.ml
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,8 @@ module Of_comments = struct

let get_value x = x.Odoc_model.Location_.value

let rec string_of_doc (doc : Odoc_model.Comment.docs) =
doc.elements |> List.map get_value
let rec string_of_doc (doc : Odoc_model.Comment.elements) =
doc |> List.map get_value
|> List.map s_of_block_element
|> String.concat "\n"

Expand Down
2 changes: 1 addition & 1 deletion src/search/text.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,6 @@

val of_type : Odoc_model.Lang.TypeExpr.t -> string

val of_doc : Odoc_model.Comment.docs -> string
val of_doc : Odoc_model.Comment.elements -> string

val of_record : Odoc_model.Lang.TypeDecl.Field.t list -> string

0 comments on commit 998b787

Please sign in to comment.