Skip to content

Commit

Permalink
Search : printing update
Browse files Browse the repository at this point in the history
  • Loading branch information
EmileTrotignon committed Jul 12, 2023
1 parent 11ae820 commit 4cf7ff8
Show file tree
Hide file tree
Showing 7 changed files with 307 additions and 257 deletions.
92 changes: 34 additions & 58 deletions src/search/entry.ml
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim

type value_entry = { value : Value.value; type_ : TypeExpr.t }

type extra =
type kind =
| TypeDecl of type_decl_entry
| Module
| Value of value_entry
Expand All @@ -61,13 +61,14 @@ module Html = Tyxml.Html
type t = {
id : Odoc_model.Paths.Identifier.Any.t;
doc : Odoc_model.Comment.docs;
extra : extra;
html : Html_types.div Html.elt;
kind : kind;
}

let entry ~id ~doc ~extra ~html =
type with_html = { entry : t; html : [ `Code | `Div ] Tyxml.Html.elt list }

let entry ~id ~doc ~kind =
let id = (id :> Odoc_model.Paths.Identifier.Any.t) in
{ id; extra; doc; html }
{ id; kind; doc }

let varify_params =
List.mapi (fun i param ->
Expand All @@ -77,15 +78,6 @@ let varify_params =

let entry_of_constructor id_parent params (constructor : TypeDecl.Constructor.t)
=
let html =
Tyxml.Html.div ~a:[]
[
Tyxml.Html.txt
@@ Generator.constructor
(constructor.id :> Identifier.t)
constructor.args constructor.res;
]
in
let args = constructor.args in
let res =
match constructor.res with
Expand All @@ -97,20 +89,11 @@ let entry_of_constructor id_parent params (constructor : TypeDecl.Constructor.t)
((id_parent :> Odoc_model.Paths.Identifier.Path.Type.t), false),
params )
in
let extra = Constructor { args; res } in
entry ~id:constructor.id ~doc:constructor.doc ~extra ~html
let kind = Constructor { args; res } in
entry ~id:constructor.id ~doc:constructor.doc ~kind

let entry_of_extension_constructor id_parent params
(constructor : Extension.Constructor.t) =
let html =
Tyxml.Html.div ~a:[]
[
Tyxml.Html.txt
@@ Generator.constructor
(constructor.id :> Identifier.t)
constructor.args constructor.res;
]
in
let args = constructor.args in
let res =
match constructor.res with
Expand All @@ -119,8 +102,8 @@ let entry_of_extension_constructor id_parent params
let params = varify_params params in
TypeExpr.Constr (id_parent, params)
in
let extra = ExtensionConstructor { args; res } in
entry ~id:constructor.id ~doc:constructor.doc ~extra ~html
let kind = ExtensionConstructor { args; res } in
entry ~id:constructor.id ~doc:constructor.doc ~kind

let entry_of_field id_parent params (field : TypeDecl.Field.t) =
let params = varify_params params in
Expand All @@ -130,49 +113,42 @@ let entry_of_field id_parent params (field : TypeDecl.Field.t) =
((id_parent :> Odoc_model.Paths.Identifier.Path.Type.t), false),
params )
in
let extra =
let kind =
Field { mutable_ = field.mutable_; type_ = field.type_; parent_type }
in
let html = Html.div ~a:[] [] in
entry ~id:field.id ~doc:field.doc ~extra ~html
entry ~id:field.id ~doc:field.doc ~kind

let rec entries_of_docs (d : Odoc_model.Comment.docs) =
List.concat_map entries_of_doc d

and entries_of_doc d =
let html = Html.div ~a:[] [] in
match d.value with
| `Paragraph (lbl, _) ->
[ entry ~id:lbl ~doc:[ d ] ~extra:(Doc Paragraph) ~html ]
| `Paragraph (lbl, _) -> [ entry ~id:lbl ~doc:[ d ] ~kind:(Doc Paragraph) ]
| `Tag _ -> []
| `List (_, ds) ->
List.concat_map entries_of_docs (ds :> Odoc_model.Comment.docs list)
| `Heading (_, lbl, _) ->
[ entry ~id:lbl ~doc:[ d ] ~extra:(Doc Heading) ~html ]
| `Heading (_, lbl, _) -> [ entry ~id:lbl ~doc:[ d ] ~kind:(Doc Heading) ]
| `Modules _ -> []
| `Code_block (lbl, _, _, o) ->
let o =
match o with
| None -> []
| Some o -> entries_of_docs (o :> Odoc_model.Comment.docs)
in
entry ~id:lbl ~doc:[ d ] ~extra:(Doc CodeBlock) ~html :: o
| `Verbatim (lbl, _) ->
[ entry ~id:lbl ~doc:[ d ] ~extra:(Doc Verbatim) ~html ]
| `Math_block (lbl, _) ->
[ entry ~id:lbl ~doc:[ d ] ~extra:(Doc MathBlock) ~html ]
entry ~id:lbl ~doc:[ d ] ~kind:(Doc CodeBlock) :: o
| `Verbatim (lbl, _) -> [ entry ~id:lbl ~doc:[ d ] ~kind:(Doc Verbatim) ]
| `Math_block (lbl, _) -> [ entry ~id:lbl ~doc:[ d ] ~kind:(Doc MathBlock) ]
| `Table _ -> []

let entries_of_item (x : Odoc_model.Fold.item) =
let html = Generator.html_of_entry x in
match x with
| CompilationUnit u -> (
match u.content with
| Module m -> [ entry ~id:u.id ~doc:m.doc ~extra:Module ~html ]
| Module m -> [ entry ~id:u.id ~doc:m.doc ~kind:Module ]
| Pack _ -> [])
| TypeDecl td ->
let txt = Render.text_of_typedecl td in
let extra =
let kind =
TypeDecl
{
txt;
Expand All @@ -181,7 +157,7 @@ let entries_of_item (x : Odoc_model.Fold.item) =
representation = td.representation;
}
in
let td_entry = entry ~id:td.id ~doc:td.doc ~extra ~html in
let td_entry = entry ~id:td.id ~doc:td.doc ~kind in
let subtype_entries =
match td.representation with
| None -> []
Expand All @@ -192,28 +168,28 @@ let entries_of_item (x : Odoc_model.Fold.item) =
| Some Extensible -> []
in
td_entry :: subtype_entries
| Module m -> [ entry ~id:m.id ~doc:m.doc ~extra:Module ~html ]
| Module m -> [ entry ~id:m.id ~doc:m.doc ~kind:Module ]
| Value v ->
let extra = Value { value = v.value; type_ = v.type_ } in
[ entry ~id:v.id ~doc:v.doc ~extra ~html ]
let kind = Value { value = v.value; type_ = v.type_ } in
[ entry ~id:v.id ~doc:v.doc ~kind ]
| Exception exc ->
let res =
Option.value exc.res
~default:(TypeExpr.Constr (Odoc_model.Predefined.exn_path, []))
in
let extra = Exception { args = exc.args; res } in
[ entry ~id:exc.id ~doc:exc.doc ~extra ~html ]
let kind = Exception { args = exc.args; res } in
[ entry ~id:exc.id ~doc:exc.doc ~kind ]
| ClassType ct ->
let extra = Class_type { virtual_ = ct.virtual_; params = ct.params } in
[ entry ~id:ct.id ~doc:ct.doc ~extra ~html ]
let kind = Class_type { virtual_ = ct.virtual_; params = ct.params } in
[ entry ~id:ct.id ~doc:ct.doc ~kind ]
| Method m ->
let extra =
let kind =
Method { virtual_ = m.virtual_; private_ = m.private_; type_ = m.type_ }
in
[ entry ~id:m.id ~doc:m.doc ~extra ~html ]
[ entry ~id:m.id ~doc:m.doc ~kind ]
| Class cl ->
let extra = Class { virtual_ = cl.virtual_; params = cl.params } in
[ entry ~id:cl.id ~doc:cl.doc ~extra ~html ]
let kind = Class { virtual_ = cl.virtual_; params = cl.params } in
[ entry ~id:cl.id ~doc:cl.doc ~kind ]
| Extension te -> (
match te.constructors with
| [] -> []
Expand All @@ -222,21 +198,21 @@ let entries_of_item (x : Odoc_model.Fold.item) =
constructor for the url. Unfortunately, this breaks the uniqueness
of the ID in the search index... *)
let type_entry =
let extra =
let kind =
TypeExtension
{
type_path = te.type_path;
type_params = te.type_params;
private_ = te.private_;
}
in
entry ~id:c.id ~doc:te.doc ~extra ~html
entry ~id:c.id ~doc:te.doc ~kind
in

type_entry
:: List.map
(entry_of_extension_constructor te.type_path te.type_params)
te.constructors)
| ModuleType mt -> [ entry ~id:mt.id ~doc:mt.doc ~extra:ModuleType ~html ]
| ModuleType mt -> [ entry ~id:mt.id ~doc:mt.doc ~kind:ModuleType ]
| Doc `Stop -> []
| Doc (`Docs d) -> entries_of_docs d
8 changes: 5 additions & 3 deletions src/search/entry.mli
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim

type value_entry = { value : Value.value; type_ : TypeExpr.t }

type extra =
type kind =
| TypeDecl of type_decl_entry
| Module
| Value of value_entry
Expand All @@ -59,8 +59,10 @@ type extra =
type t = {
id : Odoc_model.Paths.Identifier.Any.t;
doc : Odoc_model.Comment.docs;
extra : extra;
html : Html_types.div Tyxml.Html.elt;
kind : kind;
}

type with_html = { entry : t; html : [ `Code | `Div ] Tyxml.Html.elt list }
(** You can use {!Generator.with_html} to get a value of this type. *)

val entries_of_item : Odoc_model.Fold.item -> t list
Loading

0 comments on commit 4cf7ff8

Please sign in to comment.