Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,9 @@

### Added

- Addded `--suppress-warnings` to the CLI to remove warnings from a unit, even
if they end up being raised in another unit through expansion (@jonludlam,
#1260)
- Improve jump to implementation in rendered source code, and add a
`count-occurrences` flag and command to count occurrences of every identifiers
(@panglesd, #976)
Expand Down
2 changes: 0 additions & 2 deletions doc/examples/resolution.mli
Original file line number Diff line number Diff line change
Expand Up @@ -85,8 +85,6 @@ module Hidden : sig
(**/**)

type v = T of t

type w = U of u
end

module References : sig
Expand Down
2 changes: 0 additions & 2 deletions doc/odoc.mld
Original file line number Diff line number Diff line change
Expand Up @@ -59,5 +59,3 @@ The main other pages of this site:
- {!page-dune} shows how to create docs using Dune.
- {!page-parent_child_spec} delineates parent/child specifications.
- {!page-interface} describes [odoc]'s public-facing interface and their support guarantees.
- {!page-ocamlary} demonstrates the rendering of most of the OCaml constructs.
- {!page-api_reference} lists [odoc]'s API reference library.
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Why are these removed ?

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

  • interface is not removed (the end of line was removed, I'll add it back)
  • api_reference was generated by odoc's old reference driver, but is not needed now that we have the sidebar (it was just a way to make the API discoverable)
  • ocamlary was removed with the library_mlds directory, but for the sane reason we do not need it: we can find it in the sidebar.

5 changes: 5 additions & 0 deletions dune
Original file line number Diff line number Diff line change
Expand Up @@ -23,3 +23,8 @@
(progn
(bash "diff doc/driver.mld doc/driver.mld.corrected >&2 || true")
(cat doc/driver-benchmarks.json))))

(install
(files odoc-config.sexp)
(section doc)
(package odoc))
2 changes: 2 additions & 0 deletions odoc-config.sexp
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(libraries fmt)

2 changes: 1 addition & 1 deletion src/document/comment.ml
Original file line number Diff line number Diff line change
Expand Up @@ -413,7 +413,7 @@ 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

Expand Down
91 changes: 48 additions & 43 deletions src/document/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -530,8 +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) 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 @@ -608,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) 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 @@ -623,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 @@ -644,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 @@ -664,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 @@ -706,7 +706,9 @@ module Make (Syntax : SYNTAX) = struct
++
if Syntax.Type.Variant.parenthesize_params then params
else O.txt " " ++ O.keyword "of" ++ O.sp ++ params)),
match doc with [] -> None | _ -> Some (Comment.to_ir doc) ))
match doc with
| { elements = []; _ } -> None
| _ -> Some (Comment.to_ir doc.elements) ))
in
let markers = Syntax.Comment.markers in
try
Expand Down Expand Up @@ -877,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 @@ -905,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 All @@ -920,11 +922,11 @@ module Make (Syntax : SYNTAX) = struct
module Sectioning : sig
open Odoc_model

val comment_items : Comment.docs -> Item.t list
val comment_items : Comment.elements -> Item.t list

val docs : Comment.docs -> Item.t list * Item.t list
val docs : Comment.elements -> Item.t list * Item.t list
end = struct
let take_until_heading_or_end (docs : Odoc_model.Comment.docs) =
let take_until_heading_or_end (docs : Odoc_model.Comment.elements) =
let content, _, rest =
Doctree.Take.until docs ~classify:(fun b ->
match b.Location.value with
Expand All @@ -935,7 +937,7 @@ module Make (Syntax : SYNTAX) = struct
in
(content, rest)

let comment_items (input0 : Odoc_model.Comment.docs) =
let comment_items (input0 : Odoc_model.Comment.elements) =
let rec loop input_comment acc =
match input_comment with
| [] -> List.rev acc
Expand Down Expand Up @@ -1006,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 @@ -1025,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 @@ -1039,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 @@ -1048,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 All @@ -1070,11 +1072,11 @@ module Make (Syntax : SYNTAX) = struct
in
loop rest acc_items
| Comment (`Docs c) ->
let items = Sectioning.comment_items c in
let items = Sectioning.comment_items c.elements in
loop rest (List.rev_append items acc_items))
in
(* FIXME: use [t.self] *)
(c.doc, loop c.items [])
(c.doc.elements, loop c.items [])

let rec class_decl (cd : Odoc_model.Lang.Class.decl) =
match cd with
Expand Down Expand Up @@ -1111,7 +1113,8 @@ module Make (Syntax : SYNTAX) = struct
let expansion_doc, items = class_signature csig in
let url = Url.Path.from_identifier t.id in
let page =
make_expansion_page ~source_anchor url [ t.doc; expansion_doc ]
make_expansion_page ~source_anchor url
[ t.doc.elements; expansion_doc ]
items
in
( O.documentedSrc @@ path url [ inline @@ Text name ],
Expand All @@ -1132,7 +1135,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "class" ] in
let anchor = path_to_id t.id in
let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
let doc = Comment.synopsis ~decl_doc:t.doc.elements ~expansion_doc in
Item.Declaration { attr; anchor; doc; content; source_anchor }

let class_type (t : Odoc_model.Lang.ClassType.t) =
Expand All @@ -1149,7 +1152,8 @@ module Make (Syntax : SYNTAX) = struct
let url = Url.Path.from_identifier t.id in
let expansion_doc, items = class_signature csig in
let page =
make_expansion_page ~source_anchor url [ t.doc; expansion_doc ]
make_expansion_page ~source_anchor url
[ t.doc.elements; expansion_doc ]
items
in
( O.documentedSrc @@ path url [ inline @@ Text name ],
Expand All @@ -1166,14 +1170,14 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "class-type" ] in
let anchor = path_to_id t.id in
let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
let doc = Comment.synopsis ~decl_doc:t.doc.elements ~expansion_doc in
Item.Declaration { attr; anchor; doc; content; source_anchor }
end

open Class

module Module : sig
val signature : Lang.Signature.t -> Comment.Comment.docs * Item.t list
val signature : Lang.Signature.t -> Comment.Comment.elements * Item.t list
(** Returns [header_doc, content]. *)
end = struct
let internal_module m =
Expand Down Expand Up @@ -1242,7 +1246,7 @@ module Make (Syntax : SYNTAX) = struct
| Exception e -> continue @@ exn e
| Value v -> continue @@ value v
| Open o ->
let items = Sectioning.comment_items o.doc in
let items = Sectioning.comment_items o.doc.elements in
loop rest (List.rev_append items acc_items)
| Comment `Stop ->
let rest =
Expand All @@ -1252,10 +1256,10 @@ module Make (Syntax : SYNTAX) = struct
in
loop rest acc_items
| Comment (`Docs c) ->
let items = Sectioning.comment_items c in
let items = Sectioning.comment_items c.elements in
loop rest (List.rev_append items acc_items))
in
(Lang.extract_signature_doc s, loop s.items [])
((Lang.extract_signature_doc s).elements, loop s.items [])

and functor_parameter :
Odoc_model.Lang.FunctorParameter.parameter -> DocumentedSrc.t =
Expand Down Expand Up @@ -1308,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 All @@ -1319,8 +1323,8 @@ module Make (Syntax : SYNTAX) = struct
let source_anchor = None in
let modname = Paths.Identifier.name t.id in
let modname, expansion_doc, mty =
module_type_manifest ~subst:true ~source_anchor modname t.id t.doc
(Some t.manifest) prefix
module_type_manifest ~subst:true ~source_anchor modname t.id
t.doc.elements (Some t.manifest) prefix
in
let content =
O.documentedSrc (prefix ++ modname)
Expand All @@ -1330,12 +1334,12 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "module-type" ] in
let anchor = path_to_id t.id in
let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
let doc = Comment.synopsis ~decl_doc:t.doc.elements ~expansion_doc in
Item.Declaration { attr; anchor; doc; content; source_anchor }

and simple_expansion :
Odoc_model.Lang.ModuleType.simple_expansion ->
Comment.Comment.docs * Item.t list =
Comment.Comment.elements * Item.t list =
fun t ->
let rec extract_functor_params
(f : Odoc_model.Lang.ModuleType.simple_expansion) =
Expand Down Expand Up @@ -1373,7 +1377,7 @@ module Make (Syntax : SYNTAX) = struct

and expansion_of_module_type_expr :
Odoc_model.Lang.ModuleType.expr ->
(Comment.Comment.docs * Item.t list) option =
(Comment.Comment.elements * Item.t list) option =
fun t ->
let rec simple_expansion_of (t : Odoc_model.Lang.ModuleType.expr) =
match t with
Expand Down Expand Up @@ -1417,7 +1421,8 @@ module Make (Syntax : SYNTAX) = struct
let url = Url.Path.from_identifier t.id in
let link = path url [ inline @@ Text modname ] in
let page =
make_expansion_page ~source_anchor url [ t.doc; expansion_doc ]
make_expansion_page ~source_anchor url
[ t.doc.elements; expansion_doc ]
items
in
(link, status, Some page, Some expansion_doc)
Expand All @@ -1436,7 +1441,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "module" ] in
let anchor = path_to_id t.id in
let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
let doc = Comment.synopsis ~decl_doc:t.doc.elements ~expansion_doc in
Item.Declaration { attr; anchor; doc; content; source_anchor }

and simple_expansion_in_decl (base : Paths.Identifier.Module.t) se =
Expand Down Expand Up @@ -1501,8 +1506,8 @@ module Make (Syntax : SYNTAX) = struct
let modname = Paths.Identifier.name t.id in
let source_anchor = source_anchor t.source_loc in
let modname, expansion_doc, mty =
module_type_manifest ~subst:false ~source_anchor modname t.id t.doc
t.expr prefix
module_type_manifest ~subst:false ~source_anchor modname t.id
t.doc.elements t.expr prefix
in
let content =
O.documentedSrc (prefix ++ modname)
Expand All @@ -1512,7 +1517,7 @@ module Make (Syntax : SYNTAX) = struct
in
let attr = [ "module-type" ] in
let anchor = path_to_id t.id in
let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in
let doc = Comment.synopsis ~decl_doc:t.doc.elements ~expansion_doc in
Item.Declaration { attr; anchor; doc; content; source_anchor }

and umty_hidden : Odoc_model.Lang.ModuleType.U.expr -> bool = function
Expand Down Expand Up @@ -1717,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 Expand Up @@ -1772,7 +1777,7 @@ module Make (Syntax : SYNTAX) = struct
in*)
(*let title = Odoc_model.Names.PageName.to_string name in*)
let url = Url.Path.from_identifier t.name in
let preamble, items = Sectioning.docs t.content in
let preamble, items = Sectioning.docs t.content.elements in
let source_anchor = None in
Document.Page { Page.preamble; items; url; source_anchor }

Expand Down
3 changes: 2 additions & 1 deletion src/driver/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -143,6 +143,7 @@ let compile ?partial ~partial_dir (all : Odoc_unit.t list) =
in
Odoc.compile ~output_dir:unit.output_dir
~input_file:unit.input_file ~includes
~suppress_warnings:(not unit.enable_warnings)
~parent_id:unit.parent_id;
Atomic.incr Stats.stats.compiled_units;

Expand Down Expand Up @@ -191,7 +192,7 @@ let compile ?partial ~partial_dir (all : Odoc_unit.t list) =
| `Mld ->
let includes = Fpath.Set.empty in
Odoc.compile ~output_dir:unit.output_dir ~input_file:unit.input_file
~includes ~parent_id:unit.parent_id;
~includes ~suppress_warnings:false ~parent_id:unit.parent_id;
Atomic.incr Stats.stats.compiled_mlds;
Ok [ unit ]
| `Md ->
Expand Down
Loading
Loading