123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875(*
* Copyright (c) 2016 Thomas Refis <trefis@janestreet.com>
*
* Permission to use, copy, modify, and distribute this software for any
* purpose with or without fee is hereby granted, provided that the above
* copyright notice and this permission notice appear in all copies.
*
* THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
* WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
* MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
* ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
* WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
* ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
* OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
*)moduleLocation=Odoc_model.Location_modulePaths=Odoc_model.PathsopenUtilsleta_href=Tree.Relative_link.to_sub_elementletfunctor_arg_pos{Odoc_model.Lang.FunctorParameter.id;_}=matchidwith|`Argument(_,nb,_)->nb|_->failwith"TODO"(* let id = string_of_sexp @@ Identifier.sexp_of_t id in
invalid_arg (Printf.sprintf "functor_arg_pos: %s" id) *)letlabel=function|Odoc_model.Lang.TypeExpr.Labels->[Html.txts]|Optionals->[Html.txt"?";Html.entity"#8288";Html.txts]letkeywordkeyword=Html.span~a:[Html.a_class["keyword"]][Html.txtkeyword]lettype_vartv=Html.span~a:[Html.a_class["type-var"]][Html.txttv]letenclose~l~rcontent=Html.span(Html.txtl::content@[Html.txtr])includeGenerator_signatures(**
Main functor to create an {!To_html_tree.Html_generator}
*)moduleMake(Syntax:SYNTAX)=structmoduleType_expression:sigvaltype_expr:?needs_parentheses:bool->Lang.TypeExpr.t->textvalformat_type_path:delim:[`parens|`brackets]->Lang.TypeExpr.tlist->text->textend=structletrecte_variant(t:Odoc_model.Lang.TypeExpr.Polymorphic_variant.t):text=letstyle_arguments~constantarguments=(* Multiple arguments in a polymorphic variant constructor correspond
to a conjunction of types, not a product: [`Lbl int&float].
If constant is [true], the conjunction starts with an empty type,
for instance [`Lbl &int].
*)letwrapped_type_expr=(* type conjunction in Reason is printed as `Lbl (t1)&(t2)` *)ifSyntax.Type.Variant.parenthesize_paramsthenfunx->[Html.span(Html.txt"("::type_exprx@[Html.txt")"])]elsefunx->type_exprxinletarguments=list_concat_maparguments~sep:(Html.txt" & ")~f:wrapped_type_exprinifconstantthenHtml.txt"& "::argumentselseargumentsinletrecstyle_elements~add_pipe=function|[]->[]|first::rest->letfirst=matchfirstwith|Odoc_model.Lang.TypeExpr.Polymorphic_variant.Typete->letres=type_exprteinifadd_pipethen[Html.txt" ";Html.span(Html.txt"| "::res)]elseres|Constructor{constant;name;arguments;_}->letconstr=letname="`"^nameinifadd_pipethenHtml.span[Html.txt("| "^name)]elseHtml.txtnameinletres=matchargumentswith|[]->constr|_->letarguments=style_arguments~constantargumentsinHtml.span(ifSyntax.Type.Variant.parenthesize_paramsthenconstr::argumentselseconstr::Html.txt" of "::arguments)inifadd_pipethen[Html.txt" ";res]else[res]infirst@style_elements~add_pipe:truerestinletelements=style_elements~add_pipe:falset.elementsin[Html.span(matcht.kindwith|Fixed->Html.txt"[ "::elements@[Html.txt" ]"]|Open->Html.txt"[> "::elements@[Html.txt" ]"]|Closed[]->Html.txt"[< "::elements@[Html.txt" ]"]|Closedlst->letconstrs=String.concat" "lstinHtml.txt"[< "::elements@[Html.txt(" "^constrs^" ]")])]andte_object(t:Odoc_model.Lang.TypeExpr.Object.t):text=letfields=list_concat_mapt.fields~f:(function|Odoc_model.Lang.TypeExpr.Object.Method{name;type_}->(Html.txt(name^Syntax.Type.annotation_separator)::type_exprtype_)@[Html.txtSyntax.Obj.field_separator]|Inherittype_->type_exprtype_@[Html.txtSyntax.Obj.field_separator])inletopen_tag=ift.open_thenHtml.txtSyntax.Obj.open_tag_extendableelseHtml.txtSyntax.Obj.open_tag_closedinletclose_tag=ift.open_thenHtml.txtSyntax.Obj.close_tag_extendableelseHtml.txtSyntax.Obj.close_tag_closedin(open_tag::fields)@[close_tag]andformat_type_path~delim(params:Odoc_model.Lang.TypeExpr.tlist)(path:text):text=matchparamswith|[]->path|[param]->letparam=(type_expr~needs_parentheses:trueparam)inletargs=ifSyntax.Type.parenthesize_constructorthenHtml.txt"("::param@[Html.txt")"]elseparaminSyntax.Type.handle_constructor_paramspathargs|params->letparams=list_concat_mapparams~sep:(Html.txt",\194\160")~f:type_exprinletparams=matchdelimwith|`parens->enclose~l:"("params~r:")"|`brackets->enclose~l:"["params~r:"]"inSyntax.Type.handle_constructor_paramspath[params]andtype_expr?(needs_parentheses=false)(t:Odoc_model.Lang.TypeExpr.t):text=matchtwith|Vars->[type_var(Syntax.Type.var_prefix^s)]|Any->[type_varSyntax.Type.any]|Alias(te,alias)->type_expr~needs_parentheses:truete@Html.txt" "::keyword"as"::Html.txt" '"::[Html.txtalias]|Arrow(None,src,dst)->letres=type_expr~needs_parentheses:truesrc@Html.txt" "::Syntax.Type.arrow::Html.txt" "::type_exprdstinifnotneeds_parenthesesthenreselse[enclose~l:"("res~r:")"]|Arrow(Somelbl,src,dst)->letres=Html.span(labellbl@Html.txt":"::type_expr~needs_parentheses:truesrc)::Html.txt" "::Syntax.Type.arrow::Html.txt" "::type_exprdstinifnotneeds_parenthesesthenreselse[enclose~l:"("res~r:")"]|Tuplelst->letres=list_concat_maplst~sep:(Html.txtSyntax.Type.Tuple.element_separator)~f:(type_expr~needs_parentheses:true)inifSyntax.Type.Tuple.always_parenthesize||needs_parenthesesthen[enclose~l:"("res~r:")"]elseres|Constr(path,args)->letlink=Tree.Relative_link.of_path~stop_before:false(path:>Paths.Path.t)informat_type_path~delim:(`parens)argslink|Polymorphic_variantv->te_variantv|Objecto->te_objecto|Class(path,args)->format_type_path~delim:(`brackets)args(Tree.Relative_link.of_path~stop_before:false(path:>Paths.Path.t))|Poly(polyvars,t)->Html.txt(String.concat" "polyvars^". ")::type_exprt|Packagepkg->[enclose~l:"("~r:")"(keyword"module"::Html.txt" "::Tree.Relative_link.of_path~stop_before:false(pkg.path:>Paths.Path.t)@matchpkg.substitutionswith|[]->[]|lst->Html.txt" "::keyword"with"::Html.txt" "::list_concat_map_list_sep~sep:[Html.txt" ";keyword"and";Html.txt" "]lst~f:(package_substpkg.path))]andpackage_subst(pkg_path:Paths.Path.ModuleType.t)(frag_typ,te:Paths.Fragment.Type.t*Odoc_model.Lang.TypeExpr.t):text=keyword"type"::Html.txt" "::(matchpkg_pathwith|`Resolvedrp->letbase=(Paths.Path.Resolved.ModuleType.identifierrp:>Paths.Identifier.Signature.t)inTree.Relative_link.of_fragment~base(frag_typ:>Paths.Fragment.t)|_->[Html.txt(Tree.render_fragment(frag_typ:>Paths.Fragment.t))])@Html.txt" = "::type_exprteendopenType_expression(* Also handles constructor declarations for exceptions and extensible
variants, and exposes a few helpers used in formatting classes and signature
constraints. *)moduleType_declaration:sigvaltype_decl:?is_substitution:bool->Lang.Signature.recursive*Lang.TypeDecl.t->rendered_item*Odoc_model.Comment.docsvalextension:Lang.Extension.t->rendered_item*Odoc_model.Comment.docsvalexn:Lang.Exception.t->rendered_item*Odoc_model.Comment.docsvalformat_params:?delim:[`parens|`brackets]->Lang.TypeDecl.paramlist->[>`PCDATA]Html.eltvalformat_manifest:?is_substitution:bool->?compact_variants:bool->Lang.TypeDecl.Equation.t->text*boolvalformat_constraints:(Lang.TypeExpr.t*Lang.TypeExpr.t)list->textend=structletrecordfields=letfieldmutable_idtyp=matchUrl.from_identifier~stop_before:trueidwith|Errore->failwith(Url.Error.to_stringe)|Ok{anchor;kind;_}->letname=Paths.Identifier.nameidinletcell=Html.td~a:[Html.a_class["def";kind]][Html.a~a:[Html.a_href("#"^anchor);Html.a_class["anchor"]][];Html.code((ifmutable_then[keyword"mutable";Html.txt" "]else[])@(Html.txtname)::(Html.txtSyntax.Type.annotation_separator)::(type_exprtyp)@[Html.txtSyntax.Type.Record.field_separator])]inanchor,cellinletrows=fields|>List.map(funfld->letopenOdoc_model.Lang.TypeDecl.Fieldinletanchor,lhs=fieldfld.mutable_(fld.id:>Paths.Identifier.t)fld.type_inletrhs=Comment.to_htmlfld.docinletrhs=(rhs:>(Html_types.td_contentHtml.elt)list)inHtml.tr~a:[Html.a_idanchor;Html.a_class["anchored"]](lhs::ifnot(Comment.has_docfld.doc)then[]else[Html.td~a:[Html.a_class["doc"]]rhs]))in[Html.code[Html.txt"{"];Html.table~a:[Html.a_class["record"]]rows;Html.code[Html.txt"}"]]letconstructor:Paths.Identifier.t->Odoc_model.Lang.TypeDecl.Constructor.argument->Odoc_model.Lang.TypeExpr.toption->[>`Code|`PCDATA|`Table]Html.eltlist=funidargsret_type->letname=Paths.Identifier.nameidinletcstr=Html.span~a:[Html.a_class[Url.kind_of_id_exnid]][Html.txtname]inletis_gadt,ret_type=matchret_typewith|None->false,[]|Somete->letconstant=matchargswith|Tuple[]->true|_->falseinletret_type=Html.txt" "::(ifconstantthenHtml.txt":"elseSyntax.Type.GADT.arrow)::Html.txt" "::type_exprteintrue,ret_typeinmatchargswith|Tuple[]->[Html.code(cstr::ret_type)]|Tuplelst->letparams=list_concat_maplst~sep:(Html.txtSyntax.Type.Tuple.element_separator)~f:(type_expr~needs_parentheses:is_gadt)in[Html.code(cstr::(ifSyntax.Type.Variant.parenthesize_paramsthenHtml.txt"("::params@[Html.txt")"]else(ifis_gadtthen[Html.txtSyntax.Type.annotation_separator]else[Html.txt" ";keyword"of";Html.txt" "])@params)@ret_type)]|Recordfields->ifis_gadtthen(Html.code[cstr;Html.txtSyntax.Type.annotation_separator])::(recordfields)@[Html.coderet_type]else(Html.code[cstr;Html.txt" ";keyword"of";Html.txt" "])::(recordfields)letvariantcstrs:[>Html_types.table]Html.elt=letconstructoridargsres=matchUrl.from_identifier~stop_before:trueidwith|Errore->failwith(Url.Error.to_stringe)|Ok{anchor;kind;_}->letcell=Html.td~a:[Html.a_class["def";kind]](Html.a~a:[Html.a_href("#"^anchor);Html.a_class["anchor"]][]::Html.code[Html.txt"| "]::constructoridargsres)inanchor,cellinletrows=cstrs|>List.map(funcstr->letopenOdoc_model.Lang.TypeDecl.Constructorinletanchor,lhs=constructor(cstr.id:>Paths.Identifier.t)cstr.argscstr.resinletrhs=Comment.to_htmlcstr.docinletrhs=(rhs:>(Html_types.td_contentHtml.elt)list)inHtml.tr~a:[Html.a_idanchor;Html.a_class["anchored"]](lhs::ifnot(Comment.has_doccstr.doc)then[]else[Html.td~a:[Html.a_class["doc"]]rhs]))inHtml.table~a:[Html.a_class["variant"]]rowsletextension_constructor(t:Odoc_model.Lang.Extension.Constructor.t)=(* TODO doc *)constructor(t.id:>Paths.Identifier.t)t.argst.resletextension(t:Odoc_model.Lang.Extension.t)=letextension=Html.code(keyword"type"::Html.txt" "::Tree.Relative_link.of_path~stop_before:false(t.type_path:>Paths.Path.t)@[Html.txt" += "])::list_concat_mapt.constructors~sep:(Html.code[Html.txt" | "])~f:extension_constructor@(ifSyntax.Type.type_def_semicolonthen[Html.txt";"]else[])inextension,t.docletexn(t:Odoc_model.Lang.Exception.t)=letcstr=constructor(t.id:>Paths.Identifier.t)t.argst.resinletexn=Html.code[keyword"exception";Html.txt" "]::cstr@(ifSyntax.Type.Exception.semicolonthen[Html.txt";"]else[])inexn,t.docletpolymorphic_variant~type_ident(t:Odoc_model.Lang.TypeExpr.Polymorphic_variant.t)=letrowitem=letkind_approx,cstr,doc=matchitemwith|Odoc_model.Lang.TypeExpr.Polymorphic_variant.Typete->"unknown",[Html.code(type_exprte)],None|Constructor{constant;name;arguments;doc;_}->letcstr="`"^namein"constructor",beginmatchargumentswith|[]->[Html.code[Html.txtcstr]]|_->(* Multiple arguments in a polymorphic variant constructor correspond
to a conjunction of types, not a product: [`Lbl int&float].
If constant is [true], the conjunction starts with an empty type,
for instance [`Lbl &int].
*)letwrapped_type_expr=(* type conjunction in Reason is printed as `Lbl (t1)&(t2)` *)ifSyntax.Type.Variant.parenthesize_paramsthenfunx->Html.txt"("::type_exprx@[Html.txt")"]elsefunx->type_exprxinletparams=list_concat_maparguments~sep:(Html.txt" & ")~f:wrapped_type_exprinletparams=ifconstantthenHtml.txt"& "::paramselseparamsin[Html.code(Html.txtcstr::(ifSyntax.Type.Variant.parenthesize_paramsthenparamselseHtml.txt" "::keyword"of"::Html.txt" "::params))]end,matchdocwith|[]->None|_->Some(Comment.to_htmldoc:>(Html_types.td_contentHtml.elt)list)intrylet{Url.Anchor.name=anchor;kind}=Url.Anchor.Polymorphic_variant_decl.from_element~type_identiteminletconstructor_column=Html.td~a:[Html.a_class["def";kind]](Html.a~a:[Tyxml.Html.a_href("#"^anchor);Html.a_class["anchor"]][]::Html.code[Html.txt"| "]::cstr)inletcolumns=matchdocwith|None->[constructor_column]|Somedoc->[constructor_column;Html.td~a:[Html.a_class["doc"]]doc]inHtml.tr~a:[Html.a_idanchor;Html.a_class["anchored"]]columnswithFailures->Printf.eprintf"ERROR: %s\n%!"s;Html.tr[Html.td~a:[Html.a_class["def";kind_approx]](Html.code[Html.txt"| "]::cstr);]inlettable=Html.table~a:[Html.a_class["variant"]](List.maprowt.elements)inmatcht.kindwith|Fixed->Html.code[Html.txt"[ "]::table::[Html.code[Html.txt" ]"]]|Open->Html.code[Html.txt"[> "]::table::[Html.code[Html.txt" ]"]]|Closed[]->Html.code[Html.txt"[< "]::table::[Html.code[Html.txt" ]"]]|Closedlst->letconstrs=String.concat" "lstinHtml.code[Html.txt"[< "]::table::[Html.code[Html.txt(" "^constrs^" ]")]]letformat_params:'row.?delim:[`parens|`brackets]->Odoc_model.Lang.TypeDecl.paramlist->([>`PCDATA]as'row)Html.elt=fun?(delim=`parens)params->letformat_paramparam=letopenLang.TypeDeclinlet{desc;variance;injectivity}=paraminletdesc=matchdescwith|Odoc_model.Lang.TypeDecl.Any->["_"]|Vars->["'";s]inletvar_desc=matchvariancewith|None->desc|SomeOdoc_model.Lang.TypeDecl.Pos->"+"::desc|SomeOdoc_model.Lang.TypeDecl.Neg->"-"::descinletfinal=ifinjectivitythen"!"::var_descelsevar_descinString.concat""finalinHtml.txt(matchparamswith|[]->""|[x]->format_paramx|>Syntax.Type.handle_format_params|lst->letparams=String.concat", "(List.mapformat_paramlst)in(matchdelimwith`parens->"("|`brackets->"[")^params^(matchdelimwith`parens->")"|`brackets->"]"))letformat_constraintsconstraints=list_concat_mapconstraints~f:beginfun(t1,t2)->Html.txt" "::keyword"constraint"::Html.txt" "::type_exprt1@Html.txt" = "::type_exprt2endletformat_manifest:'inner_row'outer_row.?is_substitution:bool->?compact_variants:bool->Odoc_model.Lang.TypeDecl.Equation.t->text*bool=fun?(is_substitution=false)?(compact_variants=true)equation->let_=compact_variantsin(* TODO *)letprivate_=equation.private_inmatchequation.manifestwith|None->[],private_|Somet->letmanifest=Html.txt(ifis_substitutionthen" := "else" = ")::(ifprivate_then[keywordSyntax.Type.private_keyword;Html.txt" "]else[])@type_exprtinmanifest,falselettype_decl?(is_substitution=false)((recursive,t):Lang.Signature.recursive*Lang.TypeDecl.t)=lettyname=Paths.Identifier.namet.idinletparams=format_paramst.equation.paramsinletconstraints=format_constraintst.equation.constraintsinletmanifest,need_private=matcht.equation.manifestwith|Some(Odoc_model.Lang.TypeExpr.Polymorphic_variantvariant)->letmanifest=(Html.txt(ifis_substitutionthen" := "else" = ")::ift.equation.private_then[keywordSyntax.Type.private_keyword;Html.txt" "]else[])@polymorphic_variant~type_ident:(t.id:>Paths.Identifier.t)variantinmanifest,false|_->letmanifest,need_private=format_manifest~is_substitutiont.equationinUtils.optional_codemanifest,need_privateinletrepresentation=matcht.representationwith|None->[]|Somerepr->Html.code(Html.txt" = "::ifneed_privatethen[keywordSyntax.Type.private_keyword;Html.txt" "]else[])::matchreprwith|Extensible->[Html.code[Html.txt".."]]|Variantcstrs->[variantcstrs]|Recordfields->recordfieldsinlettdecl_def=letkeyword'=matchrecursivewith|Ordinary|Rec->[keyword"type"]|And->[keyword"and"]|Nonrec->[keyword"type";Html.txt" ";keyword"nonrec"]inHtml.code(keyword'@Html.txt" "::(Syntax.Type.handle_constructor_params[Html.txttyname][params]))::manifest@representation@Utils.optional_codeconstraints@(ifSyntax.Type.type_def_semicolonthen[Html.txt";"]else[])intdecl_def,t.docendopenType_declarationmoduleValue:sigvalvalue:Lang.Value.t->rendered_item*Odoc_model.Comment.docsvalexternal_:Lang.External.t->rendered_item*Odoc_model.Comment.docsend=structletvalue(t:Odoc_model.Lang.Value.t)=letname=Paths.Identifier.namet.idinletvalue=keywordSyntax.Value.variable_keyword::Html.txt" "::Html.txtname::Html.txtSyntax.Type.annotation_separator::type_exprt.type_@(ifSyntax.Value.semicolonthen[Html.txt";"]else[])in[Html.codevalue],t.docletexternal_(t:Odoc_model.Lang.External.t)=letname=Paths.Identifier.namet.idinletexternal_=keywordSyntax.Value.variable_keyword::Html.txt" "::Html.txtname::Html.txtSyntax.Type.annotation_separator::type_exprt.type_@(ifSyntax.Type.External.semicolonthen[Html.txt";"]else[])in[Html.codeexternal_],t.docendopenValuemoduleModuleSubstitution:sigvalmodule_substitution:Lang.ModuleSubstitution.t->rendered_item*Odoc_model.Comment.docsend=structletmodule_substitution(t:Odoc_model.Lang.ModuleSubstitution.t)=letname=Paths.Identifier.namet.idinletpath=Tree.Relative_link.of_path~stop_before:true(t.manifest:>Paths.Path.t)inletvalue=keyword"module"::Html.txt" "::Html.txtname::Html.txt" := "::pathin[Html.codevalue],t.docendopenModuleSubstitution(* This chunk of code is responsible for laying out signatures and class
signatures: the parts of OCaml that contain other parts as nested items.
Each item is either
- a leaf, like a type declaration or a value,
- something that has a nested signature/class signature, or
- a comment.
Comments can contain section headings, and the top-level markup code is also
responsible for generating a table of contents. As a result, it must compute
the nesting of sections.
This is also a good opportunity to properly nest everything in <section>
tags. Even though that is not strictly required by HTML, we carry out the
computation for it anyway when computing nesting for the table of
contents.
Leaf items are set in <dl> tags – the name and any definition in <dt>, and
documentation in <dd>. Multiple adjacent undocumented leaf items of the same
kind are set as sibling <dt>s in one <dl>, until one of them has
documentation. This indicates groups like:
{[
type sync
type async
(** Documentation for both types. *)
]}
Nested signatures are currently marked up with <article> tags. The top-level
layout code is eventually indirectly triggered recursively for laying them
out, as well. *)moduleTop_level_markup:sigvallay_out:item_to_id:('item->stringoption)->item_to_spec:('item->stringoption)->render_leaf_item:('item->rendered_item*Odoc_model.Comment.docs)->render_nested_article:('item->rendered_item*Odoc_model.Comment.docs*Tree.tlist)->((_,'item)tagged_item)list->(Html_types.div_contentHtml.elt)list*toc*Tree.tlistvalrender_toc:toc->([>Html_types.flow5_without_header_footer]Html.elt)listvallay_out_page:Odoc_model.Comment.docs->((Html_types.div_contentHtml.elt)list*(Html_types.flow5_without_header_footerHtml.elt)list*toc)end=struct(* Just some type abbreviations. *)typehtml=Html_types.flow5Html.elttypecomment_html=Html_types.flow5_without_header_footerHtml.eltletadd_anchoritem_to_iditemhtml=matchitem_to_iditemwith|None->html,[]|Someanchor_text->letanchor=Html.a~a:[Html.a_href("#"^anchor_text);Html.a_class["anchor"]][]inanchor::html,[Html.a_idanchor_text](* Adds spec class to the list of existing item attributes. *)letadd_specitem_to_specitema=matchitem_to_specitemwith|Somespec->Html.a_class["spec "^spec]::a|None->a(* "Consumes" adjacent leaf items of the same kind, until one is found with
documentation. Then, joins all their definitions, and the documentation of
the last item (if any), into a <dl> element. The rendered <dl> element is
paired with the list of unconsumed items remaining in the input. *)letleaf_item_groupitem_to_iditem_to_specrender_leaf_itemfirst_item_kinditems:html*'itemlist=letrecconsume_leaf_items_until_one_is_documented=funitemsacc->matchitemswith|(`Leaf_item(this_item_kind,item))::itemswhenthis_item_kind=first_item_kind->lethtml,maybe_docs=render_leaf_itemiteminlethtml,maybe_id=add_anchoritem_to_iditemhtmlinleta=add_specitem_to_specitemmaybe_idinlethtml=Html.dt~ahtmlinletacc=html::accinbeginmatchmaybe_docswith|[]->consume_leaf_items_until_one_is_documenteditemsacc|docs->letdocs=Comment.to_htmldocsinletdocs=(docs:>(Html_types.dd_contentHtml.elt)list)inletdocs=Html.dddocsinList.rev(docs::acc),itemsend|_->List.revacc,itemsinletrendered_item_group,remaining_items=consume_leaf_items_until_one_is_documenteditems[]inHtml.dlrendered_item_group,remaining_items(* When we encounter a stop comment, [(**/**)], we read everything until the
next stop comment, if there is one, and discard it. The returned item list
is the signature items following the next stop comment, if there are
any. *)letrecskip_everything_until_next_stop_comment:'itemlist->'itemlist=function|[]->[]|item::items->matchitemwith|`Comment`Stop->items|_->skip_everything_until_next_stop_commentitems(* Reads comment content until the next heading, or the end of comment, and
renders it as HTML. The returned HTML is paired with the remainder of the
comment, which will either start with the next section heading in the
comment, or be empty if there are no section headings. *)letrender_comment_until_heading_or_end:Odoc_model.Comment.docs->comment_htmllist*Odoc_model.Comment.docs=fundocs->letrecscan_commentaccdocs=matchdocswith|[]->List.revacc,docs|block::rest->matchblock.Location.valuewith|`Heading_->List.revacc,docs|_->scan_comment(block::acc)restinletincluded,remaining=scan_comment[]docsinletdocs=Comment.to_htmlincludedindocs,remaining(* The sectioning functions take several arguments, and return "modified"
instances of them as results. So, it is convenient to group them into a
record type. This is most useful for the return type, as otherwise there is
no way to give names to its components.
The components themselves are:
- The current comment being read. When non-empty, this is progressively
replaced with its tail until it is exhausted.
- The general signature items to be read. These are read one at a time when
there is no current comment. Upon encountering a comment, it becomes the
"current comment," and the sectioning functions read it one block element
at a time, scanning for section headings.
- A reversed accumulator of the rendered signature items.
- A reversed accumulator of the table of contents.
- An accumulator of the subpages generated for nested signatures.
The record is also convenient for passing around the two item-rendering
functions. *)type('kind,'item)sectioning_state={input_items:(('kind,'item)tagged_item)list;acc_subpages:Tree.tlist;comment_state:comment_state;item_to_id:'item->stringoption;item_to_spec:'item->stringoption;render_leaf_item:'item->rendered_item*Odoc_model.Comment.docs;render_nested_article:'item->rendered_item*Odoc_model.Comment.docs*Tree.tlist;}(* Comment state used to generate HTML and TOC for both mli and mld inputs. *)andcomment_state={input_comment:Odoc_model.Comment.docs;acc_html:htmllist;acc_toc:toc;}letfinish_comment_state(state:comment_state)={statewithacc_html=List.revstate.acc_html;acc_toc=List.revstate.acc_toc;}letis_deeper_section_level=letlevel_to_int=function|`Title->0|`Section->1|`Subsection->2|`Subsubsection->3|`Paragraph->4|`Subparagraph->5infunother_level~than->level_to_intother_level>level_to_intthanletrecsection_itemssection_levelstate=matchstate.input_itemswith|[]->{statewithcomment_state=finish_comment_statestate.comment_state}|tagged_item::input_items->matchtagged_itemwith|`Leaf_item(kind,_)->lethtml,input_items=leaf_item_groupstate.item_to_idstate.item_to_specstate.render_leaf_itemkindstate.input_itemsinsection_itemssection_level{statewithinput_items;comment_state={state.comment_statewithacc_html=html::state.comment_state.acc_html};}|`Nested_articleitem->lethtml,maybe_docs,subpages=state.render_nested_articleiteminlethtml,maybe_id=add_anchorstate.item_to_iditemhtmlinleta=add_specstate.item_to_specitemmaybe_idinlethtml=matchmaybe_docswith|[]->Html.div~ahtml|docs->letdocs=Comment.first_to_htmldocsinletdocs=(docs:>(Html_types.dd_contentHtml.elt)list)inHtml.dl[Html.dt~ahtml;Html.dddocs]insection_itemssection_level{statewithinput_items;comment_state={state.comment_statewithacc_html=html::state.comment_state.acc_html};acc_subpages=state.acc_subpages@subpages;}|`Comment`Stop->letinput_items=skip_everything_until_next_stop_commentinput_itemsinsection_itemssection_level{statewithinput_items;}|`Comment(`Docsinput_comment)->section_commentsection_level{statewithinput_items;comment_state={state.comment_statewithinput_comment};}andsection_commentsection_levelstate=matchstate.comment_state.input_commentwith|[]->section_itemssection_levelstate|element::input_comment->matchelement.Location.valuewith|`Heading(level,label,content)->ifnot(is_deeper_section_levellevel~than:section_level)then{statewithcomment_state=finish_comment_statestate.comment_state}else(* We have a deeper section heading in a comment within this section.
Parse it recursively. We start the nested HTML by parsing the
section heading itself, and anything that follows it in the current
comment, up to the next section heading, if any. All of this
comment matter goes into a <header> element. The nested HTML will
then be extended recursively by parsing more structure items,
including, perhaps, additional comments in <aside> elements. *)letheading_html=Comment.to_html[element]inletmore_comment_html,input_comment=render_comment_until_heading_or_endinput_commentinlethtml=Html.header(heading_html@more_comment_html)inletnested_section_state={statewithcomment_state={input_comment;acc_html=[html];acc_toc=[];}}inletnested_section_state=section_commentlevelnested_section_statein(* Wrap the nested section in a <section> element, and extend the
table of contents. *)lethtml=Html.sectionnested_section_state.comment_state.acc_htmlinlet`Label(_,label)=labelinlettoc_entry={anchor=Odoc_model.Names.LabelName.to_stringlabel;text=content;children=nested_section_state.comment_state.acc_toc;}in(* Continue parsing after the nested section. In practice, we have
either run out of items, or the first thing in the input will be
another section heading – the nested section will have consumed
everything else. *)section_commentsection_level{nested_section_statewithcomment_state={nested_section_state.comment_statewithacc_html=html::state.comment_state.acc_html;acc_toc=toc_entry::state.comment_state.acc_toc;}}|_->lethtml,input_comment=render_comment_until_heading_or_endstate.comment_state.input_commentinlethtml=(html:>(Html_types.aside_contentHtml.elt)list)insection_commentsection_level{statewithcomment_state={state.comment_statewithinput_comment;acc_html=(Html.asidehtml)::state.comment_state.acc_html;}}letlay_out~item_to_id~item_to_spec~render_leaf_item~render_nested_articleitems=letinitial_state={input_items=items;comment_state={input_comment=[];acc_html=[];acc_toc=[];};acc_subpages=[];item_to_id;item_to_spec;render_leaf_item;render_nested_article;}inletstate=section_items`Titleinitial_stateinstate.comment_state.acc_html,state.comment_state.acc_toc,state.acc_subpagesletrecpage_section_comment~header_docssection_levelstate=matchstate.input_commentwith|[]->{statewithacc_toc=List.revstate.acc_toc},header_docs|element::input_comment->beginmatchelement.Location.valuewith|`Heading(`Title,_label,_content)->letheading_html=Comment.to_html[element]inletmore_comment_html,input_comment=render_comment_until_heading_or_endinput_commentinletheader_docs=heading_html@more_comment_htmlinletnested_section_state={input_comment=input_comment;acc_html=[];acc_toc=[];}inletnested_section_state,header_docs=page_section_comment~header_docs`Sectionnested_section_stateinletacc_html=state.acc_html@nested_section_state.acc_htmlinpage_section_comment~header_docssection_level{nested_section_statewithacc_html}|`Heading(level,_label,_content)whennot(is_deeper_section_levellevel~than:section_level)->{statewithacc_toc=List.revstate.acc_toc},header_docs|`Heading(level,label,content)->letheading_html=Comment.to_html[element]inletmore_comment_html,input_comment=render_comment_until_heading_or_endinput_commentinletacc_html=heading_html@more_comment_htmlinletacc_html=(acc_html:>(Html_types.flow5Html.elt)list)inletnested_section_state={input_comment=input_comment;acc_html;acc_toc=[];}inletnested_section_state,header_docs=page_section_comment~header_docslevelnested_section_stateinletacc_html=state.acc_html@nested_section_state.acc_htmlinletacc_toc=let`Label(_,label)=labelinlettoc_entry={anchor=Odoc_model.Names.LabelName.to_stringlabel;text=content;children=nested_section_state.acc_toc;}intoc_entry::state.acc_tocinpage_section_comment~header_docssection_level{nested_section_statewithacc_html;acc_toc}|_->lethtml,input_comment=render_comment_until_heading_or_endstate.input_commentinlethtml=(html:>(Html_types.flow5Html.elt)list)inpage_section_comment~header_docssection_level{statewithinput_comment;acc_html=html@state.acc_html;}endletlay_out_pageinput_comment=letinitial_state:comment_state={input_comment;acc_html=[];acc_toc=[];}inletstate,header_docs=page_section_comment~header_docs:[]`Titleinitial_stateinstate.acc_html,header_docs,state.acc_tocletrender_toctoc=letrecsectionthe_section:Html_types.li_contentHtml.eltlist=lettext=Comment.link_content_to_htmlthe_section.textinlettext=(text:Html_types.phrasing_without_interactiveHtml.eltlist:>(Html_types.flow5_without_interactiveHtml.elt)list)inletlink=Html.a~a:[Html.a_href("#"^the_section.anchor)]textinmatchthe_section.childrenwith|[]->[link]|_->[link;sectionsthe_section.children]andsectionsthe_sections=the_sections|>List.map(funthe_section->Html.li(sectionthe_section))|>Html.ulinmatchtocwith|[]->[]|_->[Html.nav~a:[Html.a_class["toc"]][sectionstoc]]end(* TODO Figure out when this function would fail. It is currently pasted from
[make_def], but the [make_spec] version doesn't have a [failwith]. *)letpath_to_idpath=matchUrl.from_identifier~stop_before:truepathwith|Error_->None|Ok{anchor;_}->SomeanchormoduleClass:sigvalclass_:?theme_uri:Tree.uri->Lang.Signature.recursive->Lang.Class.t->rendered_item*Odoc_model.Comment.docs*Tree.tlistvalclass_type:?theme_uri:Tree.uri->Lang.Signature.recursive->Lang.ClassType.t->rendered_item*Odoc_model.Comment.docs*Tree.tlistend=structletclass_signature_item_to_id:Lang.ClassSignature.item->_=function|Method{id;_}->path_to_id(id:>Paths.Identifier.t)|InstanceVariable{id;_}->path_to_id(id:>Paths.Identifier.t)|Constraint_|Inherit_|Comment_->Noneletclass_signature_item_to_spec:Lang.ClassSignature.item->_=function|Method_->Some"method"|InstanceVariable_->Some"instance-variable"|Constraint_|Inherit_|Comment_->Nonelettag_class_signature_item:Lang.ClassSignature.item->_=funitem->matchitemwith|Method_->`Leaf_item(`Method,item)|InstanceVariable_->`Leaf_item(`Variable,item)|Constraint_->`Leaf_item(`Constraint,item)|Inherit_->`Leaf_item(`Inherit,item)|Commentcomment->`Commentcommentletrecrender_class_signature_item:Lang.ClassSignature.item->text*_=function|Methodm->method_m|InstanceVariablev->instance_variablev|Constraint(t1,t2)->format_constraints[(t1,t2)],[]|Inherit(Signature_)->assertfalse(* Bold. *)|Inheritclass_type_expression->[Html.code(keyword"inherit"::Html.txt" "::class_type_exprclass_type_expression)],[]|Comment_->assertfalseandclass_signature(c:Lang.ClassSignature.t)=(* FIXME: use [t.self] *)lettagged_items=List.maptag_class_signature_itemc.itemsinTop_level_markup.lay_out~item_to_id:class_signature_item_to_id~item_to_spec:class_signature_item_to_spec~render_leaf_item:(funitem->lettext,docs=render_class_signature_itemitemin(text:>rendered_item),docs)~render_nested_article:(fun_->assertfalse)tagged_itemsandmethod_(t:Odoc_model.Lang.Method.t)=letname=Paths.Identifier.namet.idinletvirtual_=ift.virtual_then[keyword"virtual";Html.txt" "]else[]inletprivate_=ift.private_then[keyword"private";Html.txt" "]else[]inletmethod_=keyword"method"::Html.txt" "::private_@virtual_@Html.txtname::Html.txtSyntax.Type.annotation_separator::type_exprt.type_in[Html.codemethod_],t.docandinstance_variable(t:Odoc_model.Lang.InstanceVariable.t)=letname=Paths.Identifier.namet.idinletvirtual_=ift.virtual_then[keyword"virtual";Html.txt" "]else[]inletmutable_=ift.mutable_then[keyword"mutable";Html.txt" "]else[]inletval_=keyword"val"::Html.txt" "::mutable_@virtual_@Html.txtname::Html.txtSyntax.Type.annotation_separator::type_exprt.type_in[Html.codeval_],t.docandclass_type_expr(cte:Odoc_model.Lang.ClassType.expr)=matchctewith|Constr(path,args)->letlink=Tree.Relative_link.of_path~stop_before:false(path:>Paths.Path.t)informat_type_path~delim:(`brackets)argslink|Signature_->[Syntax.Class.open_tag;Html.txt" ... ";Syntax.Class.close_tag]andclass_decl(cd:Odoc_model.Lang.Class.decl)=matchcdwith|ClassTypeexpr->class_type_exprexpr(* TODO: factorize the following with [type_expr] *)|Arrow(None,src,dst)->type_expr~needs_parentheses:truesrc@Html.txt" "::Syntax.Type.arrow::Html.txt" "::class_decldst|Arrow(Somelbl,src,dst)->labellbl@Html.txt":"::type_expr~needs_parentheses:truesrc@Html.txt" "::Syntax.Type.arrow::Html.txt" "::class_decldstandclass_?theme_urirecursive(t:Odoc_model.Lang.Class.t)=letname=Paths.Identifier.namet.idinletparams=format_params~delim:(`brackets)t.paramsinletvirtual_=ift.virtual_then[keyword"virtual";Html.txt" "]else[]inletcd=class_declt.type_inletcname,subtree=matcht.expansionwith|None->Html.txtname,[]|Somecsig->Tree.enter~kind:(`Class)name;letdoc=Comment.to_htmlt.docinletexpansion,toc,_=class_signaturecsiginletheader_docs=matchtocwith|[]->doc|_->doc@(Top_level_markup.render_toctoc)inletsubtree=Tree.make~header_docs?theme_uriexpansion[]inTree.leave();Html.a~a:[a_href~kind:`Classname][Html.txtname],[subtree]inletclass_def_content=letopenLang.Signatureinletkeyword'=matchrecursivewith|Ordinary|Nonrec|Rec->"class"|And->"and"inkeywordkeyword'::Html.txt" "::virtual_@params::Html.txt" "::cname::Html.txtSyntax.Type.annotation_separator::cdinletregion=[Html.codeclass_def_content]inregion,t.doc,subtreeandclass_type?theme_urirecursive(t:Odoc_model.Lang.ClassType.t)=letname=Paths.Identifier.namet.idinletparams=format_params~delim:(`brackets)t.paramsinletvirtual_=ift.virtual_then[keyword"virtual";Html.txt" "]else[]inletexpr=class_type_exprt.exprinletcname,subtree=matcht.expansionwith|None->Html.txtname,[]|Somecsig->Tree.enter~kind:(`Cty)name;letdoc=Comment.to_htmlt.docinletexpansion,_,_=class_signaturecsiginletsubtree=Tree.make~header_docs:doc?theme_uriexpansion[]inTree.leave();Html.a~a:[a_href~kind:`Ctyname][Html.txtname],[subtree]inletctyp=letopenLang.Signatureinletkeyword'=matchrecursivewith|Ordinary|Nonrec|Rec->[keyword"class";Html.txt" ";keyword"type"]|And->[keyword"and"]inkeyword'@[Html.txt" "]@virtual_@params::Html.txt" "::cname::Html.txt" = "::exprinletregion=[Html.codectyp]inregion,t.doc,subtreeendopenClassmoduleModule:sigvalsignature:?theme_uri:Tree.uri->Lang.Signature.t->(Html_types.div_contentHtml.elt)list*toc*Tree.tlistend=structletsignature_item_to_id:Lang.Signature.item->_=function|Type(_,{id;_})->path_to_id(id:>Paths.Identifier.t)|TypeSubstitution{id;_}->path_to_id(id:>Paths.Identifier.t)|Exception{id;_}->path_to_id(id:>Paths.Identifier.t)|Value{id;_}->path_to_id(id:>Paths.Identifier.t)|External{id;_}->path_to_id(id:>Paths.Identifier.t)|Module(_,{id;_})->path_to_id(id:>Paths.Identifier.t)|ModuleType{id;_}->path_to_id(id:>Paths.Identifier.t)|ModuleSubstitution{id;_}->path_to_id(id:>Paths.Identifier.t)|Class(_,{id;_})->path_to_id(id:>Paths.Identifier.t)|ClassType(_,{id;_})->path_to_id(id:>Paths.Identifier.t)|TypExt_|Include_|Comment_->Noneletsignature_item_to_spec:Lang.Signature.item->_=function|Type_->Some"type"|TypeSubstitution_->Some"type-subst"|Exception_->Some"exception"|Value_->Some"value"|External_->Some"external"|Module_->Some"module"|ModuleType_->Some"module-type"|ModuleSubstitution_->Some"module-substitution"|Class_->Some"class"|ClassType_->Some"class-type"|TypExt_->Some"extension"|Include_|Comment_->Nonelettag_signature_item:Lang.Signature.item->_=funitem->matchitemwith|Type_->`Leaf_item(`Type,item)|TypeSubstitution_->`Leaf_item(`TypeSubstitution,item)|TypExt_->`Leaf_item(`Extension,item)|Exception_->`Leaf_item(`Exception,item)|Value_->`Leaf_item(`Value,item)|External_->`Leaf_item(`External,item)|ModuleSubstitution_->`Leaf_item(`ModuleSubstitution,item)|Module_|ModuleType_|Include_|Class_|ClassType_->`Nested_articleitem|Commentcomment->`Commentcommentletrecrender_leaf_signature_item:Lang.Signature.item->_=function|Type(r,t)->type_decl(r,t)|TypeSubstitutiont->type_decl~is_substitution:true(Ordinary,t)|TypExte->extensione|Exceptione->exne|Valuev->valuev|Externale->external_e|ModuleSubstitutionm->module_substitutionm|_->assertfalseandrender_nested_signature_or_class:?theme_uri:Tree.uri->Lang.Signature.item->_=fun?theme_uriitem->matchitemwith|Module(recursive,m)->module_?theme_urirecursivem|ModuleTypem->module_type?theme_urim|Class(recursive,c)->class_?theme_urirecursivec|ClassType(recursive,c)->class_type?theme_urirecursivec|Includem->include_?theme_urim|_->assertfalseandsignature?theme_uris=lettagged_items=List.maptag_signature_itemsinTop_level_markup.lay_out~item_to_id:signature_item_to_id~item_to_spec:signature_item_to_spec~render_leaf_item:render_leaf_signature_item~render_nested_article:(render_nested_signature_or_class?theme_uri)tagged_itemsandfunctor_argument:'row.?theme_uri:Tree.uri->Odoc_model.Lang.FunctorParameter.parameter->Html_types.div_contentHtml.eltlist*Tree.tlist=fun?theme_uriarg->letopenOdoc_model.Lang.FunctorParameterinletname=Paths.Identifier.namearg.idinletnb=functor_arg_posarginletlink_name=Printf.sprintf"%d-%s"nbnameinletdef_div,subtree=matcharg.expansionwith|None->(Html.txt(Paths.Identifier.namearg.id)::Html.txtSyntax.Type.annotation_separator::mty(arg.id:>Paths.Identifier.Signature.t)arg.expr),[]|Someexpansion->letexpansion=matchexpansionwith|AlreadyASig->beginmatcharg.exprwith|Signaturesg->Odoc_model.Lang.Module.Signaturesg|_->assertfalseend|e->einTree.enter~kind:(`Arg)link_name;let(doc,toc,subpages)=module_expansion?theme_uriexpansioninletheader_docs=Top_level_markup.render_toctocinletsubtree=Tree.make~header_docs?theme_uridocsubpagesinTree.leave();(Html.a~a:[a_href~kind:`Arglink_name][Html.txtname]::Html.txtSyntax.Type.annotation_separator::mty(arg.id:>Paths.Identifier.Signature.t)arg.expr),[subtree]inletregion=[Html.codedef_div]inregion,subtreeandmodule_expansion:?theme_uri:Tree.uri->Odoc_model.Lang.Module.expansion->Html_types.div_content_funHtml.eltlist*toc*Tree.tlist=fun?theme_urit->matchtwith|AlreadyASig->assertfalse|Signaturesg->letexpansion,toc,subpages=signature?theme_urisginexpansion,toc,subpages|Functor(args,sg)->letsig_html,toc,subpages=signature?theme_urisginletparams,params_subpages=List.fold_left(fun(args,subpagesasacc)arg->matchargwith|Odoc_model.Lang.FunctorParameter.Unit->acc|Namedarg->letarg,arg_subpages=functor_argument?theme_uriarginletarg=Html.liargin(args@[arg],subpages@arg_subpages))([],[])argsinlethtml=Html.h3~a:[Html.a_class["heading"]][Html.txt"Parameters"]::Html.ul(List.mapHtml.Unsafe.coerce_eltparams)::Html.h3~a:[Html.a_class["heading"]][Html.txt"Signature"]::sig_htmlinhtml,toc,params_subpages@subpagesandmodule_:?theme_uri:Tree.uri->Odoc_model.Lang.Signature.recursive->Odoc_model.Lang.Module.t->rendered_item*Odoc_model.Comment.docs*Tree.tlist=fun?theme_urirecursivet->letmodname=Paths.Identifier.namet.idinletmd=module_decl(t.id:>Paths.Identifier.Signature.t)(matcht.display_typewith|None->t.type_|Somet->t)inletmodname,subtree=matcht.expansionwith|None->Html.txtmodname,[]|Someexpansion->letexpansion=matchexpansionwith|AlreadyASig->beginmatcht.type_with|ModuleType(Odoc_model.Lang.ModuleType.Signaturesg)->Odoc_model.Lang.Module.Signaturesg|_->assertfalseend|e->einTree.enter~kind:(`Mod)modname;letdoc=Comment.to_htmlt.docinletexpansion,toc,subpages=module_expansion?theme_uriexpansioninletheader_docs=matchtocwith|[]->doc|_->doc@(Top_level_markup.render_toctoc)inletsubtree=Tree.make~header_docs?theme_uriexpansionsubpagesinTree.leave();Html.a~a:[a_href~kind:`Modmodname][Html.txtmodname],[subtree]inletmd_def_content=letkeyword'=matchrecursivewith|Ordinary|Nonrec->[keyword"module"]|Rec->[keyword"module";Html.txt" ";keyword"rec"]|And->[keyword"and"]inkeyword'@Html.txt" "::modname::md@(ifSyntax.Mod.close_tag_semicolonthen[Html.txt";"]else[])inletregion=[Html.codemd_def_content]inregion,t.doc,subtreeandmodule_decl(base:Paths.Identifier.Signature.t)md=beginmatchmdwith|Alias_->Html.txt" = "|ModuleType_->Html.txtSyntax.Type.annotation_separatorend::module_decl'basemdandextract_path_from_mt~(default:Paths.Identifier.Signature.t)=letopenOdoc_model.Lang.ModuleTypeinfunction|Path(`Resolvedr)->(Paths.Path.Resolved.ModuleType.identifierr:>Paths.Identifier.Signature.t)|With(mt,_)->extract_path_from_mt~defaultmt|TypeOf(Odoc_model.Lang.Module.Alias(`Resolvedr))->(Paths.Path.Resolved.Module.identifierr:>Paths.Identifier.Signature.t)|TypeOf(Odoc_model.Lang.Module.ModuleTypemt)->extract_path_from_mt~defaultmt|_->defaultandmodule_decl':Paths.Identifier.Signature.t->Odoc_model.Lang.Module.decl->text=funbase->function|Aliasmod_path->Tree.Relative_link.of_path~stop_before:true(mod_path:>Paths.Path.t)|ModuleTypemt->mty(extract_path_from_mt~default:basemt)mtandmodule_type?theme_uri(t:Odoc_model.Lang.ModuleType.t)=letmodname=Paths.Identifier.namet.idinletmty=matcht.exprwith|None->[]|Someexpr->Html.txt" = "::mty(t.id:>Paths.Identifier.Signature.t)exprinletmodname,subtree=matcht.expansionwith|None->Html.txtmodname,[]|Someexpansion->letexpansion=matchexpansionwith|AlreadyASig->beginmatcht.exprwith|Some(Signaturesg)->Odoc_model.Lang.Module.Signaturesg|_->assertfalseend|e->einTree.enter~kind:(`Mty)modname;letdoc=Comment.to_htmlt.docinletexpansion,toc,subpages=module_expansion?theme_uriexpansioninletheader_docs=matchtocwith|[]->doc|_->doc@(Top_level_markup.render_toctoc)inletsubtree=Tree.make~header_docs?theme_uriexpansionsubpagesinTree.leave();Html.a~a:[a_href~kind:`Mtymodname][Html.txtmodname],[subtree]inletmty_def=(keyword"module"::Html.txt" "::keyword"type"::Html.txt" "::modname::mty@(ifSyntax.Mod.close_tag_semicolonthen[Html.txt";"]else[]))inletregion=[Html.codemty_def]inregion,t.doc,subtreeandmty:Paths.Identifier.Signature.t->Odoc_model.Lang.ModuleType.expr->text=funbase->function|Pathmty_path->Tree.Relative_link.of_path~stop_before:true(mty_path:>Paths.Path.t)|Signature_->[Syntax.Mod.open_tag;Html.txt" ... ";Syntax.Mod.close_tag;]|Functor(Unit,expr)->(ifSyntax.Mod.functor_keywordthen[keyword"functor"]else[])@Html.txt" () "::mtybaseexpr|Functor(Namedarg,expr)->letname=letopenOdoc_model.Lang.FunctorParameterinletto_print=Html.txt@@Paths.Identifier.namearg.idinmatchTree.Relative_link.Id.href~stop_before:(arg.expansion=None)(arg.id:>Paths.Identifier.t)with|exception_->to_print|href->Html.a~a:[Html.a_hrefhref][to_print]in(ifSyntax.Mod.functor_keywordthen[keyword"functor"]else[])@Html.txt" ("::name::Html.txtSyntax.Type.annotation_separator::mtybasearg.expr@[Html.txt")";Html.txt" "]@Syntax.Type.arrow::Html.txt" "::mtybaseexpr|With(expr,substitutions)->mtybaseexpr@Html.txt" "::keyword"with"::Html.txt" "::list_concat_map_list_sep~sep:[Html.txt" ";keyword"and";Html.txt" "]~f:(substitutionbase)substitutions|TypeOfmd->keyword"module"::Html.txt" "::keyword"type"::Html.txt" "::keyword"of"::Html.txt" "::module_decl'basemdandsubstitution:Paths.Identifier.Signature.t->Odoc_model.Lang.ModuleType.substitution->text=funbase->function|ModuleEq(frag_mod,md)->keyword"module"::Html.txt" "::Tree.Relative_link.of_fragment~base(frag_mod:>Paths.Fragment.t)@Html.txt" = "::module_decl'basemd|TypeEq(frag_typ,td)->keyword"type"::Html.txt" "::(Syntax.Type.handle_substitution_params(Tree.Relative_link.of_fragment~base(frag_typ:>Paths.Fragment.t))[format_paramstd.Lang.TypeDecl.Equation.params])@fst(format_manifesttd)@format_constraintstd.Odoc_model.Lang.TypeDecl.Equation.constraints|ModuleSubst(frag_mod,mod_path)->keyword"module"::Html.txt" "::Tree.Relative_link.of_fragment~base(frag_mod:>Paths.Fragment.t)@Html.txt" := "::Tree.Relative_link.of_path~stop_before:true(mod_path:>Paths.Path.t)|TypeSubst(frag_typ,td)->keyword"type"::Html.txt" "::(Syntax.Type.handle_substitution_params(Tree.Relative_link.of_fragment~base(frag_typ:>Paths.Fragment.t))[format_paramstd.Lang.TypeDecl.Equation.params])@Html.txt" := "::matchtd.Lang.TypeDecl.Equation.manifestwith|None->assertfalse(* cf loader/cmti *)|Somete->type_exprteandinclude_?theme_uri(t:Odoc_model.Lang.Include.t)=letdocs=Comment.to_htmlt.docinletdocs=(docs:>(Html_types.div_contentHtml.elt)list)inletincluded_html,_,tree=signature?theme_urit.expansion.contentinletshould_be_inlined=letis_inline_tagelement=element.Odoc_model.Location_.value=`Tag`InlineinList.existsis_inline_tagt.docinletshould_be_open=letis_open_tagelement=element.Odoc_model.Location_.value=`Tag`Openinletis_closed_tagelement=element.Odoc_model.Location_.value=`Tag`ClosedinifList.existsis_open_tagt.docthentrueelse!Tree.open_details&¬(List.existsis_closed_tagt.doc)inletincl=ifshould_be_inlinedthenincluded_htmlelseletincl=Html.code(keyword"include"::Html.txt" "::module_decl't.parentt.decl@(ifSyntax.Mod.include_semicolonthen[keyword";"]else[]))in(* FIXME: I'd like to add an anchor here, but I don't know what id to
give it... *)[Html.details~a:(ifshould_be_openthen[Html.a_open()]else[])(Html.summary[Html.span~a:[Html.a_class["def"]][incl]])included_html]in[Html.div~a:[Html.a_class["spec";"include"]][Html.div~a:[Html.a_class["doc"]](docs@incl)]],[],treeendopenModulemodulePage:sigvalcompilation_unit:?theme_uri:Tree.uri->Lang.Compilation_unit.t->Tree.tvalpage:?theme_uri:Tree.uri->Lang.Page.t->Tree.tend=structletpack:Odoc_model.Lang.Compilation_unit.Packed.t->Html_types.div_contentHtml.eltlist=funt->letopenOdoc_model.Langint|>List.mapbeginfunx->letmodname=Paths.Identifier.namex.Compilation_unit.Packed.idinletmd_def=keyword"module"::Html.txt" "::Html.txtmodname::Html.txt" = "::Tree.Relative_link.of_path~stop_before:false(x.path:>Paths.Path.t)in[Html.codemd_def]end|>List.flatten|>fundefinitions->[Html.articledefinitions]letcompilation_unit?theme_uri(t:Odoc_model.Lang.Compilation_unit.t):Tree.t=letpackage=matcht.idwith|`Root(a,_)->a.package|_->assertfalseinTree.enterpackage;Tree.enter(Paths.Identifier.namet.id);letheader_docs=Comment.to_htmlt.docinletheader_docs,html,subtree=matcht.contentwith|Modulesign->lethtml,toc,subpages=signature?theme_urisigninletheader_docs=matchtocwith|[]->header_docs|_->header_docs@(Top_level_markup.render_toctoc)inheader_docs,html,subpages|Packpacked->header_docs,packpacked,[]inTree.make~header_docs?theme_urihtmlsubtreeletpage?theme_uri(t:Odoc_model.Lang.Page.t):Tree.t=letpackage,name=matcht.namewith|`Page(a,name)->a.package,nameinTree.enterpackage;Tree.enter~kind:`Page(Odoc_model.Names.PageName.to_stringname);lethtml,header_docs,toc=Top_level_markup.lay_out_paget.contentinlethtml=(html:>(Html_types.div_contentHtml.elt)list)inletheader_docs=matchtocwith|[]->header_docs|_->header_docs@(Top_level_markup.render_toctoc)inTree.make~header_docs?theme_urihtml[]endincludePageend