Skip to content

Commit

Permalink
Label boolean argument for loading functions
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Dec 13, 2024
1 parent 998b787 commit c63fc05
Show file tree
Hide file tree
Showing 6 changed files with 8 additions and 8 deletions.
2 changes: 1 addition & 1 deletion src/loader/cmt.ml
Original file line number Diff line number Diff line change
Expand Up @@ -616,7 +616,7 @@ and read_structure :
| _ ->
({ Signature.items = Comment (`Docs doc_post) :: items; compiled=false; removed = []; doc }, tags)

let read_implementation root name suppress_warnings impl =
let read_implementation root name ~suppress_warnings impl =
let id =
Identifier.Mk.root (root, Odoc_model.Names.ModuleName.make_std name)
in
Expand Down
2 changes: 1 addition & 1 deletion src/loader/cmt.mli
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@
val read_implementation :
Odoc_model.Paths.Identifier.ContainerPage.t option ->
string ->
bool ->
suppress_warnings:bool ->
Typedtree.structure ->
Odoc_model.Paths.Identifier.RootModule.t
* Odoc_model.Lang.Signature.t
Expand Down
2 changes: 1 addition & 1 deletion src/loader/cmti.ml
Original file line number Diff line number Diff line change
Expand Up @@ -815,7 +815,7 @@ and read_signature :
| _ ->
({ Signature.items = Comment (`Docs doc_post) :: items; compiled=false; removed = []; doc }, tags)

let read_interface root name suppress_warnings intf =
let read_interface root name ~suppress_warnings intf =
let id =
Identifier.Mk.root (root, Odoc_model.Names.ModuleName.make_std name)
in
Expand Down
2 changes: 1 addition & 1 deletion src/loader/cmti.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ val read_module_expr :
val read_interface :
Odoc_model.Paths.Identifier.ContainerPage.t option ->
string ->
bool ->
suppress_warnings:bool ->
Typedtree.signature ->
Paths.Identifier.RootModule.t
* Odoc_model.Lang.Signature.t
Expand Down
4 changes: 2 additions & 2 deletions src/loader/odoc_loader.ml
Original file line number Diff line number Diff line change
Expand Up @@ -119,7 +119,7 @@ let read_cmti ~make_root ~parent ~filename ~suppress_warnings () =
cmt_info.cmt_builddir )
in
let id, sg, canonical =
Cmti.read_interface parent name suppress_warnings intf
Cmti.read_interface parent name ~suppress_warnings intf
in
compilation_unit_of_sig ~make_root ~imports:cmt_info.cmt_imports
~interface ~sourcefile ~name ~id ?canonical sg)
Expand Down Expand Up @@ -178,7 +178,7 @@ let read_cmt ~make_root ~parent ~filename ~suppress_warnings () =
~id content
| Implementation impl ->
let id, sg, canonical =
Cmt.read_implementation parent name suppress_warnings impl
Cmt.read_implementation parent name ~suppress_warnings impl
in
compilation_unit_of_sig ~make_root ~imports ~interface ~sourcefile
~name ~id ?canonical sg
Expand Down
4 changes: 2 additions & 2 deletions test/xref2/lib/common.cppo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -70,15 +70,15 @@ let root_pp fmt (_ : Odoc_model.Root.t) = Format.fprintf fmt "Common.root"

let model_of_string str =
let cmti = cmti_of_string str in
Odoc_loader__Cmti.read_interface (Some parent) "Root" false cmti
Odoc_loader__Cmti.read_interface (Some parent) "Root" ~suppress_warnings:false cmti

let model_of_string_impl str =
#if OCAML_VERSION < (4,13,0)
let (cmt,_) = cmt_of_string str in
#else
let cmt = (cmt_of_string str).structure in
#endif
Odoc_loader__Cmt.read_implementation (Some parent) "Root" false cmt
Odoc_loader__Cmt.read_implementation (Some parent) "Root" ~suppress_warnings:false cmt

let signature_of_mli_string str =
Odoc_xref2.Ident.reset ();
Expand Down

0 comments on commit c63fc05

Please sign in to comment.