123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833(**************************************************************************)(* *)(* OCaml *)(* *)(* Thomas Gazagnaire, OCamlPro *)(* Fabrice Le Fessant, INRIA Saclay *)(* Hongbo Zhang, University of Pennsylvania *)(* *)(* Copyright 2007 Institut National de Recherche en Informatique et *)(* en Automatique. *)(* *)(* All rights reserved. This file is distributed under the terms of *)(* the GNU Lesser General Public License version 2.1, with the *)(* special exception on linking described in the file LICENSE. *)(* *)(**************************************************************************)(* Original Code from Ber-metaocaml, modified for 3.12.0 and fixed *)(* Printing code expressions *)(* Authors: Ed Pizzi, Fabrice Le Fessant *)(* Extensive Rewrite: Hongbo Zhang: University of Pennsylvania *)(* TODO more fine-grained precedence pretty-printing *)openAsttypesopenFormatopenLocationopenLongidentopenParsetreeletprefix_symbols=['!';'?';'~']letinfix_symbols=['=';'<';'>';'@';'^';'|';'&';'+';'-';'*';'/';'$';'%';'#'](* type fixity = Infix| Prefix *)letspecial_infix_strings=["asr";"land";"lor";"lsl";"lsr";"lxor";"mod";"or";":=";"!=";"::"]letletops=String.lengths>3&&s.[0]='l'&&s.[1]='e'&&s.[2]='t'&&List.mems.[3]infix_symbolsletandops=String.lengths>3&&s.[0]='a'&&s.[1]='n'&&s.[2]='d'&&List.mems.[3]infix_symbols(* determines if the string is an infix string.
checks backwards, first allowing a renaming postfix ("_102") which
may have resulted from Pexp -> Texp -> Pexp translation, then checking
if all the characters in the beginning of the string are valid infix
characters. *)letfixity_of_string=function|""->`Normal|swhenList.memsspecial_infix_strings->`Infixs|swhenList.mems.[0]infix_symbols->`Infixs|swhenList.mems.[0]prefix_symbols->`Prefixs|swhens.[0]='.'->`Mixfixs|swhenletops->`Letops|swhenandops->`Andops|_->`Normalletview_fixity_of_exp=function|{pexp_desc=Pexp_ident{txt=Lidentl;_};pexp_attributes=[]}->fixity_of_stringl|_->`Normalletis_infix=function`Infix_->true|_->falseletis_mixfix=function`Mixfix_->true|_->falseletis_kwdop=function`Letop_|`Andop_->true|_->falseletfirst_iscstr=str<>""&&str.[0]=cletlast_iscstr=str<>""&&str.[String.lengthstr-1]=cletfirst_is_incsstr=str<>""&&List.memstr.[0]cs(* which identifiers are in fact operators needing parentheses *)letneeds_parenstxt=letfix=fixity_of_stringtxtinis_infixfix||is_mixfixfix||is_kwdopfix||first_is_inprefix_symbolstxt(* some infixes need spaces around parens to avoid clashes with comment
syntax *)letneeds_spacestxt=first_is'*'txt||last_is'*'txt(* Turn an arbitrary variable name into a valid OCaml identifier by adding \#
in case it is a keyword, or parenthesis when it is an infix or prefix
operator. *)letident_of_nameppftxt=letformat:(_,_,_)format=ifLexer.is_keywordtxtthen"\\#%s"elseifnot(needs_parenstxt)then"%s"elseifneeds_spacestxtthen"(@;%s@;)"else"(%s)"infprintfppfformattxtletident_of_name_locppfs=ident_of_nameppfs.txtletprotect_longidentppfprint_longidentlongprefixtxt=ifnot(needs_parenstxt)thenfprintfppf"%a.%a"print_longidentlongprefixident_of_nametxtelseifneeds_spacestxtthenfprintfppf"%a.(@;%s@;)"print_longidentlongprefixtxtelsefprintfppf"%a.(%s)"print_longidentlongprefixtxttypespace_formatter=(unit,Format.formatter,unit)formatletoverride=function|Override->"!"|Fresh->""(* variance encoding: need to sync up with the [parser.mly] *)lettype_variance=function|NoVariance->""|Covariant->"+"|Contravariant->"-"lettype_injectivity=function|NoInjectivity->""|Injective->"!"typeconstruct=[`consofexpressionlist|`listofexpressionlist|`nil|`normal|`simpleofLongident.t|`tuple|`btrue|`bfalse]letview_exprx=matchx.pexp_descwith|Pexp_construct({txt=Lident"()";_},_)->`tuple|Pexp_construct({txt=Lident"true";_},_)->`btrue|Pexp_construct({txt=Lident"false";_},_)->`bfalse|Pexp_construct({txt=Lident"[]";_},_)->`nil|Pexp_construct({txt=Lident"::";_},Some_)->letrecloopexpacc=matchexpwith|{pexp_desc=Pexp_construct({txt=Lident"[]";_},_);pexp_attributes=[]}->(List.revacc,true)|{pexp_desc=Pexp_construct({txt=Lident"::";_},Some({pexp_desc=Pexp_tuple([e1;e2]);pexp_attributes=[]}));pexp_attributes=[]}->loope2(e1::acc)|e->(List.rev(e::acc),false)inlet(ls,b)=loopx[]inifbthen`listlselse`consls|Pexp_construct(x,None)->`simple(x.txt)|_->`normalletis_simple_construct:construct->bool=function|`nil|`tuple|`list_|`simple_|`btrue|`bfalse->true|`cons_|`normal->falseletpp=fprintftypectxt={pipe:bool;semi:bool;ifthenelse:bool;functionrhs:bool;}letreset_ctxt={pipe=false;semi=false;ifthenelse=false;functionrhs=false}letunder_pipectxt={ctxtwithpipe=true}letunder_semictxt={ctxtwithsemi=true}letunder_ifthenelsectxt={ctxtwithifthenelse=true}letunder_functionrhsctxt={ctxtwithfunctionrhs=true}(*
let reset_semi ctxt = { ctxt with semi=false }
let reset_ifthenelse ctxt = { ctxt with ifthenelse=false }
let reset_pipe ctxt = { ctxt with pipe=false }
*)letlist:'a.?sep:space_formatter->?first:space_formatter->?last:space_formatter->(Format.formatter->'a->unit)->Format.formatter->'alist->unit=fun?sep?first?lastfufxs->letfirst=matchfirstwithSomex->x|None->("":_format6)andlast=matchlastwithSomex->x|None->("":_format6)andsep=matchsepwithSomex->x|None->("@ ":_format6)inletauxf=function|[]->()|[x]->fufx|xs->letrecloopf=function|[x]->fufx|x::xs->fufx;ppfsep;loopfxs;|_->assertfalseinbeginppffirst;loopfxs;ppflast;endinauxfxsletoption:'a.?first:space_formatter->?last:space_formatter->(Format.formatter->'a->unit)->Format.formatter->'aoption->unit=fun?first?lastfufa->letfirst=matchfirstwithSomex->x|None->("":_format6)andlast=matchlastwithSomex->x|None->("":_format6)inmatchawith|None->()|Somex->ppffirst;fufx;ppflastletparen:'a.?first:space_formatter->?last:space_formatter->bool->(Format.formatter->'a->unit)->Format.formatter->'a->unit=fun?(first=("":_format6))?(last=("":_format6))bfufx->ifbthen(ppf"(";ppffirst;fufx;ppflast;ppf")")elsefufxletreclongidentf=function|Lidents->ident_of_namefs|Ldot(y,s)->protect_longidentflongidentys|Lapply(y,s)->ppf"%a(%a)"longidentylongidentsletlongident_locfx=ppf"%a"longidentx.txtletconstantf=function|Pconst_chari->ppf"%C"i|Pconst_string(i,_,None)->ppf"%S"i|Pconst_string(i,_,Somedelim)->ppf"{%s|%s|%s}"delimidelim|Pconst_integer(i,None)->paren(first_is'-'i)(funf->ppf"%s")fi|Pconst_integer(i,Somem)->paren(first_is'-'i)(funf(i,m)->ppf"%s%c"im)f(i,m)|Pconst_float(i,None)->paren(first_is'-'i)(funf->ppf"%s")fi|Pconst_float(i,Somem)->paren(first_is'-'i)(funf(i,m)->ppf"%s%c"im)f(i,m)(* trailing space*)letmutable_flagf=function|Immutable->()|Mutable->ppf"mutable@;"letvirtual_flagf=function|Concrete->()|Virtual->ppf"virtual@;"(* trailing space added *)letrec_flagfrf=matchrfwith|Nonrecursive->()|Recursive->ppf"rec "letnonrec_flagfrf=matchrfwith|Nonrecursive->ppf"nonrec "|Recursive->()letdirection_flagf=function|Upto->ppf"to@ "|Downto->ppf"downto@ "letprivate_flagf=function|Public->()|Private->ppf"private@ "letiter_locfctxt{txt;loc=_}=fctxttxtletconstant_stringfs=ppf"%S"slettyvar_of_names=ifString.lengths>=2&&s.[1]='\''then(* without the space, this would be parsed as
a character literal *)"' "^selseifLexer.is_keywordsthen"'\\#"^selseifString.equals"_"thenselse"'"^slettyvarppfs=Format.fprintfppf"%s"(tyvar_of_names)lettyvar_locfstr=tyvarfstr.txtletstring_quotfx=ppf"`%a"ident_of_namex(* c ['a,'b] *)letrecclass_params_defctxtf=function|[]->()|l->ppf"[%a] "(* space *)(list(type_paramctxt)~sep:",")landtype_with_labelctxtf(label,c)=matchlabelwith|Nolabel->core_type1ctxtfc(* otherwise parenthesize *)|Labelleds->ppf"%a:%a"ident_of_names(core_type1ctxt)c|Optionals->ppf"?%a:%a"ident_of_names(core_type1ctxt)candcore_typectxtfx=ifx.ptyp_attributes<>[]thenbeginppf"((%a)%a)"(core_typectxt){xwithptyp_attributes=[]}(attributesctxt)x.ptyp_attributesendelsematchx.ptyp_descwith|Ptyp_arrow(l,ct1,ct2)->ppf"@[<2>%a@;->@;%a@]"(* FIXME remove parens later *)(type_with_labelctxt)(l,ct1)(core_typectxt)ct2|Ptyp_alias(ct,s)->ppf"@[<2>%a@;as@;%a@]"(core_type1ctxt)cttyvars.txt|Ptyp_poly([],ct)->core_typectxtfct|Ptyp_poly(sl,ct)->ppf"@[<2>%a%a@]"(funfl->matchlwith|[]->()|_->ppf"%a@;.@;"(listtyvar_loc~sep:"@;")l)sl(core_typectxt)ct|_->ppf"@[<2>%a@]"(core_type1ctxt)xandcore_type1ctxtfx=ifx.ptyp_attributes<>[]thencore_typectxtfxelsematchx.ptyp_descwith|Ptyp_any->ppf"_";|Ptyp_vars->tyvarfs;|Ptyp_tuplel->ppf"(%a)"(list(core_type1ctxt)~sep:"@;*@;")l|Ptyp_constr(li,l)->ppf(* "%a%a@;" *)"%a%a"(funfl->matchlwith|[]->()|[x]->ppf"%a@;"(core_type1ctxt)x|_->list~first:"("~last:")@;"(core_typectxt)~sep:",@;"fl)llongident_locli|Ptyp_variant(l,closed,low)->letfirst_is_inherit=matchlwith|{Parsetree.prf_desc=Rinherit_}::_->true|_->falseinlettype_variant_helperfx=matchx.prf_descwith|Rtag(l,_,ctl)->ppf"@[<2>%a%a@;%a@]"(iter_locstring_quot)l(funfl->matchlwith|[]->()|_->ppf"@;of@;%a"(list(core_typectxt)~sep:"&")ctl)ctl(attributesctxt)x.prf_attributes|Rinheritct->core_typectxtfctinppf"@[<2>[%a%a]@]"(funfl->matchl,closedwith|[],Closed->()|[],Open->ppf">"(* Cf #7200: print [>] correctly *)|_->ppf"%s@;%a"(match(closed,low)with|(Closed,None)->iffirst_is_inheritthen" |"else""|(Closed,Some_)->"<"(* FIXME desugar the syntax sugar*)|(Open,_)->">")(listtype_variant_helper~sep:"@;<1 -2>| ")l)l(funflow->matchlowwith|Some[]|None->()|Somexs->ppf">@ %a"(liststring_quot)xs)low|Ptyp_object(l,o)->letcore_field_typefx=matchx.pof_descwith|Otag(l,ct)->(* Cf #7200 *)ppf"@[<hov2>%a: %a@ %a@ @]"ident_of_namel.txt(core_typectxt)ct(attributesctxt)x.pof_attributes|Oinheritct->ppf"@[<hov2>%a@ @]"(core_typectxt)ctinletfield_varf=function|Asttypes.Closed->()|Asttypes.Open->matchlwith|[]->ppf".."|_->ppf" ;.."inppf"@[<hov2><@ %a%a@ > @]"(listcore_field_type~sep:";")lfield_varo(* Cf #7200 *)|Ptyp_class(li,l)->(*FIXME*)ppf"@[<hov2>%a#%a@]"(list(core_typectxt)~sep:","~first:"("~last:")")llongident_locli|Ptyp_package(lid,cstrs)->letauxf(s,ct)=ppf"type %a@ =@ %a"longident_locs(core_typectxt)ctin(matchcstrswith|[]->ppf"@[<hov2>(module@ %a)@]"longident_loclid|_->ppf"@[<hov2>(module@ %a@ with@ %a)@]"longident_loclid(listaux~sep:"@ and@ ")cstrs)|Ptyp_open(li,ct)->ppf"@[<hov2>%a.(%a)@]"longident_locli(core_typectxt)ct|Ptyp_extensione->extensionctxtfe|(Ptyp_arrow_|Ptyp_alias_|Ptyp_poly_)->parentrue(core_typectxt)fx(********************pattern********************)(* be cautious when use [pattern], [pattern1] is preferred *)andpatternctxtfx=ifx.ppat_attributes<>[]thenbeginppf"((%a)%a)"(patternctxt){xwithppat_attributes=[]}(attributesctxt)x.ppat_attributesendelsematchx.ppat_descwith|Ppat_alias(p,s)->ppf"@[<2>%a@;as@;%a@]"(patternctxt)pident_of_names.txt|_->pattern_orctxtfxandpattern_orctxtfx=letrecleft_associativexacc=matchxwith|{ppat_desc=Ppat_or(p1,p2);ppat_attributes=[]}->left_associativep1(p2::acc)|x->x::accinmatchleft_associativex[]with|[]->assertfalse|[x]->pattern1ctxtfx|orpats->ppf"@[<hov0>%a@]"(list~sep:"@ | "(pattern1ctxt))orpatsandpattern1ctxt(f:Format.formatter)(x:pattern):unit=letrecpattern_list_helperf=function|{ppat_desc=Ppat_construct({txt=Lident("::");_},Some([],{ppat_desc=Ppat_tuple([pat1;pat2]);_}));ppat_attributes=[]}->ppf"%a::%a"(simple_patternctxt)pat1pattern_list_helperpat2(*RA*)|p->pattern1ctxtfpinifx.ppat_attributes<>[]thenpatternctxtfxelsematchx.ppat_descwith|Ppat_variant(l,Somep)->ppf"@[<2>`%a@;%a@]"ident_of_namel(simple_patternctxt)p|Ppat_construct(({txt=Lident("()"|"[]"|"true"|"false");_}),_)->simple_patternctxtfx|Ppat_construct(({txt;_}asli),po)->(* FIXME The third field always false *)iftxt=Lident"::"thenppf"%a"pattern_list_helperxelse(matchpowith|Some([],x)->ppf"%a@;%a"longident_locli(simple_patternctxt)x|Some(vl,x)->ppf"%a@ (type %a)@;%a"longident_locli(list~sep:"@ "ident_of_name_loc)vl(simple_patternctxt)x|None->ppf"%a"longident_locli)|_->simple_patternctxtfxandsimple_patternctxt(f:Format.formatter)(x:pattern):unit=ifx.ppat_attributes<>[]thenpatternctxtfxelsematchx.ppat_descwith|Ppat_construct(({txt=Lident("()"|"[]"|"true"|"false"asx);_}),None)->ppf"%s"x|Ppat_any->ppf"_";|Ppat_var({txt=txt;_})->ident_of_nameftxt|Ppat_arrayl->ppf"@[<2>[|%a|]@]"(list(pattern1ctxt)~sep:";")l|Ppat_unpack{txt=None}->ppf"(module@ _)@ "|Ppat_unpack{txt=Somes}->ppf"(module@ %s)@ "s|Ppat_typeli->ppf"#%a"longident_locli|Ppat_record(l,closed)->letlongident_x_patternf(li,p)=match(li,p)with|({txt=Lidents;_},{ppat_desc=Ppat_var{txt;_};ppat_attributes=[];_})whens=txt->ppf"@[<2>%a@]"longident_locli|_->ppf"@[<2>%a@;=@;%a@]"longident_locli(pattern1ctxt)pinbeginmatchclosedwith|Closed->ppf"@[<2>{@;%a@;}@]"(listlongident_x_pattern~sep:";@;")l|_->ppf"@[<2>{@;%a;_}@]"(listlongident_x_pattern~sep:";@;")lend|Ppat_tuplel->ppf"@[<1>(%a)@]"(list~sep:",@;"(pattern1ctxt))l(* level1*)|Ppat_constant(c)->ppf"%a"constantc|Ppat_interval(c1,c2)->ppf"%a..%a"constantc1constantc2|Ppat_variant(l,None)->ppf"`%a"ident_of_namel|Ppat_constraint(p,ct)->ppf"@[<2>(%a@;:@;%a)@]"(pattern1ctxt)p(core_typectxt)ct|Ppat_lazyp->ppf"@[<2>(lazy@;%a)@]"(simple_patternctxt)p|Ppat_exceptionp->ppf"@[<2>exception@;%a@]"(pattern1ctxt)p|Ppat_extensione->extensionctxtfe|Ppat_open(lid,p)->letwith_paren=matchp.ppat_descwith|Ppat_array_|Ppat_record_|Ppat_construct(({txt=Lident("()"|"[]"|"true"|"false");_}),None)->false|_->trueinppf"@[<2>%a.%a @]"longident_loclid(parenwith_paren@@pattern1ctxt)p|_->parentrue(patternctxt)fxandlabel_expctxtf(l,opt,p)=matchlwith|Nolabel->(* single case pattern parens needed here *)ppf"%a@ "(simple_patternctxt)p|Optionalrest->beginmatchpwith|{ppat_desc=Ppat_var{txt;_};ppat_attributes=[]}whentxt=rest->(matchoptwith|Someo->ppf"?(%a=@;%a)@;"ident_of_namerest(expressionctxt)o|None->ppf"?%a@ "ident_of_namerest)|_->(matchoptwith|Someo->ppf"?%a:(%a=@;%a)@;"ident_of_namerest(pattern1ctxt)p(expressionctxt)o|None->ppf"?%a:%a@;"ident_of_namerest(simple_patternctxt)p)end|Labelledl->matchpwith|{ppat_desc=Ppat_var{txt;_};ppat_attributes=[]}whentxt=l->ppf"~%a@;"ident_of_namel|_->ppf"~%a:%a@;"ident_of_namel(simple_patternctxt)pandsugar_exprctxtfe=ife.pexp_attributes<>[]thenfalseelsematche.pexp_descwith|Pexp_apply({pexp_desc=Pexp_ident{txt=id;_};pexp_attributes=[];_},args)whenList.for_all(fun(lab,_)->lab=Nolabel)args->beginletprint_indexopapath_prefixassignleftseprightprint_indexindicesrem_args=letprint_pathppf=function|None->()|Somem->ppppf".%a"longidentminmatchassign,rem_argswith|false,[]->ppf"@[%a%a%s%a%s@]"(simple_exprctxt)aprint_pathpath_prefixleft(list~sepprint_index)indicesright;true|true,[v]->ppf"@[%a%a%s%a%s@ <-@;<1 2>%a@]"(simple_exprctxt)aprint_pathpath_prefixleft(list~sepprint_index)indicesright(simple_exprctxt)v;true|_->falseinmatchid,List.mapsndargswith|Lident"!",[e]->ppf"@[<hov>!%a@]"(simple_exprctxt)e;true|Ldot(path,("get"|"set"asfunc)),a::other_args->beginletassign=func="set"inletprint=print_indexopaNoneassigninmatchpath,other_argswith|Lident"Array",i::rest->print".("""")"(expressionctxt)[i]rest|Lident"String",i::rest->print".[""""]"(expressionctxt)[i]rest|Ldot(Lident"Bigarray","Array1"),i1::rest->print".{"",""}"(simple_exprctxt)[i1]rest|Ldot(Lident"Bigarray","Array2"),i1::i2::rest->print".{"",""}"(simple_exprctxt)[i1;i2]rest|Ldot(Lident"Bigarray","Array3"),i1::i2::i3::rest->print".{"",""}"(simple_exprctxt)[i1;i2;i3]rest|Ldot(Lident"Bigarray","Genarray"),{pexp_desc=Pexp_arrayindexes;pexp_attributes=[]}::rest->print".{"",""}"(simple_exprctxt)indexesrest|_->falseend|(Lidents|Ldot(_,s)),a::i::restwhenfirst_is'.'s->(* extract operator:
assignment operators end with [right_bracket ^ "<-"],
access operators end with [right_bracket] directly
*)letmulti_indices=String.containss';'inleti=matchi.pexp_descwith|Pexp_arraylwhenmulti_indices->l|_->[i]inletassign=last_is'-'sinletkind=(* extract the right end bracket *)letn=String.lengthsinifassignthens.[n-3]elses.[n-1]inletleft,right=matchkindwith|')'->'(',")"|']'->'[',"]"|'}'->'{',"}"|_->assertfalseinletpath_prefix=matchidwith|Ldot(m,_)->Somem|_->Noneinletleft=String.subs0(1+String.indexsleft)inprint_indexopapath_prefixassignleft";"right(ifmulti_indicesthenexpressionctxtelsesimple_exprctxt)irest|_->falseend|_->falseandfunction_paramctxtfparam=matchparam.pparam_descwith|Pparam_val(a,b,c)->label_expctxtf(a,b,c)|Pparam_newtypety->ppf"(type %a)@;"ident_of_namety.txtandfunction_bodyctxtffunction_body=matchfunction_bodywith|Pfunction_bodybody->expressionctxtfbody|Pfunction_cases(cases,_,attrs)->ppf"@[<hv>function%a%a@]"(item_attributesctxt)attrs(case_listctxt)casesandtype_constraintctxtfconstraint_=matchconstraint_with|Pconstraintty->ppf":@;%a"(core_typectxt)ty|Pcoerce(ty1,ty2)->ppf"%a:>@;%a"(option~first:":@;"(core_typectxt))ty1(core_typectxt)ty2andfunction_params_then_bodyctxtfparamsconstraint_body~delimiter=ppf"%a%a%s@;%a"(list(function_paramctxt)~sep:"")params(option(type_constraintctxt))constraint_delimiter(function_body(under_functionrhsctxt))bodyandexpressionctxtfx=ifx.pexp_attributes<>[]thenppf"((%a)@,%a)"(expressionctxt){xwithpexp_attributes=[]}(attributesctxt)x.pexp_attributeselsematchx.pexp_descwith|Pexp_function_|Pexp_match_|Pexp_try_|Pexp_sequence_|Pexp_newtype_whenctxt.pipe||ctxt.semi->parentrue(expressionreset_ctxt)fx|Pexp_ifthenelse_|Pexp_sequence_whenctxt.ifthenelse->parentrue(expressionreset_ctxt)fx|Pexp_let_|Pexp_letmodule_|Pexp_open_|Pexp_letexception_|Pexp_letop_whenctxt.semi->parentrue(expressionreset_ctxt)fx|Pexp_newtype(lid,e)->ppf"@[<2>fun@;(type@;%a)@;->@;%a@]"ident_of_namelid.txt(expressionctxt)e|Pexp_function(params,c,body)->beginmatchparams,cwith(* Omit [fun] if there are no params. *)|[],None->(* If function cases are a direct body of a function,
the function node should be wrapped in parens so
it doesn't become part of the enclosing function. *)letshould_paren=matchbodywith|Pfunction_cases_->ctxt.functionrhs|Pfunction_body_->falseinletctxt'=ifshould_parenthenreset_ctxtelsectxtinppf"@[<2>%a@]"(parenshould_paren(function_bodyctxt'))body|[],Somec->ppf"@[<2>(%a@;%a)@]"(function_bodyctxt)body(type_constraintctxt)c|_::_,_->ppf"@[<2>fun@;%a@]"(funf()->function_params_then_bodyctxtfparamscbody~delimiter:"->")();end|Pexp_match(e,l)->ppf"@[<hv0>@[<hv0>@[<2>match %a@]@ with@]%a@]"(expressionreset_ctxt)e(case_listctxt)l|Pexp_try(e,l)->ppf"@[<0>@[<hv2>try@ %a@]@ @[<0>with%a@]@]"(* "try@;@[<2>%a@]@\nwith@\n%a"*)(expressionreset_ctxt)e(case_listctxt)l|Pexp_let(rf,l,e)->(* pp f "@[<2>let %a%a in@;<1 -2>%a@]"
(*no indentation here, a new line*) *)(* rec_flag rf *)ppf"@[<2>%a in@;<1 -2>%a@]"(bindingsreset_ctxt)(rf,l)(expressionctxt)e|Pexp_apply(e,l)->beginifnot(sugar_exprctxtfx)thenmatchview_fixity_of_expewith|`Infixs->beginmatchlwith|[(Nolabel,_)asarg1;(Nolabel,_)asarg2]->(* FIXME associativity label_x_expression_param *)ppf"@[<2>%a@;%s@;%a@]"(label_x_expression_paramreset_ctxt)arg1s(label_x_expression_paramctxt)arg2|_->ppf"@[<2>%a %a@]"(simple_exprctxt)e(list(label_x_expression_paramctxt))lend|`Prefixs->lets=ifList.mems["~+";"~-";"~+.";"~-."]&&(matchlwith(* See #7200: avoid turning (~- 1) into (- 1) which is
parsed as an int literal *)|[(_,{pexp_desc=Pexp_constant_})]->false|_->true)thenString.subs1(String.lengths-1)elsesinbeginmatchlwith|[(Nolabel,x)]->ppf"@[<2>%s@;%a@]"s(simple_exprctxt)x|_->ppf"@[<2>%a %a@]"(simple_exprctxt)e(list(label_x_expression_paramctxt))lend|_->ppf"@[<hov2>%a@]"beginfunf(e,l)->ppf"%a@ %a"(expression2ctxt)e(list(label_x_expression_paramreset_ctxt))l(* reset here only because [function,match,try,sequence]
are lower priority *)end(e,l)end|Pexp_construct(li,Someeo)whennot(is_simple_construct(view_exprx))->(* Not efficient FIXME*)(matchview_exprxwith|`consls->list(simple_exprctxt)fls~sep:"@;::@;"|`normal->ppf"@[<2>%a@;%a@]"longident_locli(simple_exprctxt)eo|_->assertfalse)|Pexp_setfield(e1,li,e2)->ppf"@[<2>%a.%a@ <-@ %a@]"(simple_exprctxt)e1longident_locli(simple_exprctxt)e2|Pexp_ifthenelse(e1,e2,eo)->(* @;@[<2>else@ %a@]@] *)letfmt:(_,_,_)format="@[<hv0>@[<2>if@ %a@]@;@[<2>then@ %a@]%a@]"inletexpression_under_ifthenelse=expression(under_ifthenelsectxt)inppffmtexpression_under_ifthenelsee1expression_under_ifthenelsee2(funfeo->matcheowith|Somex->ppf"@;@[<2>else@;%a@]"(expression(under_semictxt))x|None->()(* pp f "()" *))eo|Pexp_sequence_->letrecsequence_helperacc=function|{pexp_desc=Pexp_sequence(e1,e2);pexp_attributes=[]}->sequence_helper(e1::acc)e2|v->List.rev(v::acc)inletlst=sequence_helper[]xinppf"@[<hv>%a@]"(list(expression(under_semictxt))~sep:";@;")lst|Pexp_new(li)->ppf"@[<hov2>new@ %a@]"longident_locli;|Pexp_setinstvar(s,e)->ppf"@[<hov2>%a@ <-@ %a@]"ident_of_names.txt(expressionctxt)e|Pexp_overridel->(* FIXME *)letstring_x_expressionf(s,e)=ppf"@[<hov2>%a@ =@ %a@]"ident_of_names.txt(expressionctxt)einppf"@[<hov2>{<%a>}@]"(liststring_x_expression~sep:";")l;|Pexp_letmodule(s,me,e)->ppf"@[<hov2>let@ module@ %s@ =@ %a@ in@ %a@]"(Option.values.txt~default:"_")(module_exprreset_ctxt)me(expressionctxt)e|Pexp_letexception(cd,e)->ppf"@[<hov2>let@ exception@ %a@ in@ %a@]"(extension_constructorctxt)cd(expressionctxt)e|Pexp_asserte->ppf"@[<hov2>assert@ %a@]"(simple_exprctxt)e|Pexp_lazy(e)->ppf"@[<hov2>lazy@ %a@]"(simple_exprctxt)e(* Pexp_poly: impossible but we should print it anyway, rather than
assert false *)|Pexp_poly(e,None)->ppf"@[<hov2>!poly!@ %a@]"(simple_exprctxt)e|Pexp_poly(e,Somect)->ppf"@[<hov2>(!poly!@ %a@ : %a)@]"(simple_exprctxt)e(core_typectxt)ct|Pexp_open(o,e)->ppf"@[<2>let open%s %a in@;%a@]"(overrideo.popen_override)(module_exprctxt)o.popen_expr(expressionctxt)e|Pexp_variant(l,Someeo)->ppf"@[<2>`%a@;%a@]"ident_of_namel(simple_exprctxt)eo|Pexp_letop{let_;ands;body}->ppf"@[<2>@[<v>%a@,%a@] in@;<1 -2>%a@]"(binding_opctxt)let_(list~sep:"@,"(binding_opctxt))ands(expressionctxt)body|Pexp_extension({txt;_},_)whentxt=Ast_helper.hole_txt->ppf"%a"(simple_exprctxt)x|Pexp_extensione->extensionctxtfe|Pexp_unreachable->ppf"."|_->expression1ctxtfxandexpression1ctxtfx=ifx.pexp_attributes<>[]thenexpressionctxtfxelsematchx.pexp_descwith|Pexp_objectcs->ppf"%a"(class_structurectxt)cs|_->expression2ctxtfx(* used in [Pexp_apply] *)andexpression2ctxtfx=ifx.pexp_attributes<>[]thenexpressionctxtfxelsematchx.pexp_descwith|Pexp_field(e,li)->ppf"@[<hov2>%a.%a@]"(simple_exprctxt)elongident_locli|Pexp_send(e,s)->ppf"@[<hov2>%a#%a@]"(simple_exprctxt)eident_of_names.txt|_->simple_exprctxtfxandsimple_exprctxtfx=ifx.pexp_attributes<>[]thenexpressionctxtfxelsematchx.pexp_descwith|Pexp_construct_whenis_simple_construct(view_exprx)->(matchview_exprxwith|`nil->ppf"[]"|`tuple->ppf"()"|`btrue->ppf"true"|`bfalse->ppf"false"|`listxs->ppf"@[<hv0>[%a]@]"(list(expression(under_semictxt))~sep:";@;")xs|`simplex->longidentfx|_->assertfalse)|Pexp_identli->longident_locfli(* (match view_fixity_of_exp x with *)(* |`Normal -> longident_loc f li *)(* | `Prefix _ | `Infix _ -> pp f "( %a )" longident_loc li) *)|Pexp_constantc->constantfc;|Pexp_packme->ppf"(module@;%a)"(module_exprctxt)me|Pexp_tuplel->ppf"@[<hov2>(%a)@]"(list(simple_exprctxt)~sep:",@;")l|Pexp_constraint(e,ct)->ppf"(%a : %a)"(expressionctxt)e(core_typectxt)ct|Pexp_coerce(e,cto1,ct)->ppf"(%a%a :> %a)"(expressionctxt)e(option(core_typectxt)~first:" : "~last:" ")cto1(* no sep hint*)(core_typectxt)ct|Pexp_variant(l,None)->ppf"`%a"ident_of_namel|Pexp_record(l,eo)->letlongident_x_expressionf(li,e)=matchewith|{pexp_desc=Pexp_ident{txt;_};pexp_attributes=[];_}whenli.txt=txt->ppf"@[<hov2>%a@]"longident_locli|_->ppf"@[<hov2>%a@;=@;%a@]"longident_locli(simple_exprctxt)einppf"@[<hv0>@[<hv2>{@;%a%a@]@;}@]"(* "@[<hov2>{%a%a}@]" *)(option~last:" with@;"(simple_exprctxt))eo(listlongident_x_expression~sep:";@;")l|Pexp_array(l)->ppf"@[<0>@[<2>[|%a|]@]@]"(list(simple_expr(under_semictxt))~sep:";")l|Pexp_while(e1,e2)->letfmt:(_,_,_)format="@[<2>while@;%a@;do@;%a@;done@]"inppffmt(expressionctxt)e1(expressionctxt)e2|Pexp_for(s,e1,e2,df,e3)->letfmt:(_,_,_)format="@[<hv0>@[<hv2>@[<2>for %a =@;%a@;%a%a@;do@]@;%a@]@;done@]"inletexpression=expressionctxtinppffmt(patternctxt)sexpressione1direction_flagdfexpressione2expressione3|Pexp_extension({txt;_},_)whentxt=Ast_helper.hole_txt->ppf"_"|_->parentrue(expressionctxt)fxandattributesctxtfl=List.iter(attributectxtf)landitem_attributesctxtfl=List.iter(item_attributectxtf)landattributectxtfa=ppf"@[<2>[@@%s@ %a]@]"a.attr_name.txt(payloadctxt)a.attr_payloadanditem_attributectxtfa=ppf"@[<2>[@@@@%s@ %a]@]"a.attr_name.txt(payloadctxt)a.attr_payloadandfloating_attributectxtfa=ppf"@[<2>[@@@@@@%s@ %a]@]"a.attr_name.txt(payloadctxt)a.attr_payloadandvalue_descriptionctxtfx=(* note: value_description has an attribute field,
but they're already printed by the callers this method *)ppf"@[<hov2>%a%a@]"(core_typectxt)x.pval_type(funfx->ifx.pval_prim<>[]thenppf"@ =@ %a"(listconstant_string)x.pval_prim)xandextensionctxtf(s,e)=ppf"@[<2>[%%%s@ %a]@]"s.txt(payloadctxt)eanditem_extensionctxtf(s,e)=ppf"@[<2>[%%%%%s@ %a]@]"s.txt(payloadctxt)eandexception_declarationctxtfx=ppf"@[<hov2>exception@ %a@]%a"(extension_constructorctxt)x.ptyexn_constructor(item_attributesctxt)x.ptyexn_attributesandclass_type_fieldctxtfx=matchx.pctf_descwith|Pctf_inherit(ct)->ppf"@[<2>inherit@ %a@]%a"(class_typectxt)ct(item_attributesctxt)x.pctf_attributes|Pctf_val(s,mf,vf,ct)->ppf"@[<2>val @ %a%a%a@ :@ %a@]%a"mutable_flagmfvirtual_flagvfident_of_names.txt(core_typectxt)ct(item_attributesctxt)x.pctf_attributes|Pctf_method(s,pf,vf,ct)->ppf"@[<2>method %a %a%a :@;%a@]%a"private_flagpfvirtual_flagvfident_of_names.txt(core_typectxt)ct(item_attributesctxt)x.pctf_attributes|Pctf_constraint(ct1,ct2)->ppf"@[<2>constraint@ %a@ =@ %a@]%a"(core_typectxt)ct1(core_typectxt)ct2(item_attributesctxt)x.pctf_attributes|Pctf_attributea->floating_attributectxtfa|Pctf_extensione->item_extensionctxtfe;item_attributesctxtfx.pctf_attributesandclass_signaturectxtf{pcsig_self=ct;pcsig_fields=l;_}=ppf"@[<hv0>@[<hv2>object@[<1>%a@]@ %a@]@ end@]"(funf->function{ptyp_desc=Ptyp_any;ptyp_attributes=[];_}->()|ct->ppf" (%a)"(core_typectxt)ct)ct(list(class_type_fieldctxt)~sep:"@;")l(* call [class_signature] called by [class_signature] *)andclass_typectxtfx=matchx.pcty_descwith|Pcty_signaturecs->class_signaturectxtfcs;attributesctxtfx.pcty_attributes|Pcty_constr(li,l)->ppf"%a%a%a"(funfl->matchlwith|[]->()|_->ppf"[%a]@ "(list(core_typectxt)~sep:",")l)llongident_locli(attributesctxt)x.pcty_attributes|Pcty_arrow(l,co,cl)->ppf"@[<2>%a@;->@;%a@]"(* FIXME remove parens later *)(type_with_labelctxt)(l,co)(class_typectxt)cl|Pcty_extensione->extensionctxtfe;attributesctxtfx.pcty_attributes|Pcty_open(o,e)->ppf"@[<2>let open%s %a in@;%a@]"(overrideo.popen_override)longident_loco.popen_expr(class_typectxt)e(* [class type a = object end] *)andclass_type_declaration_listctxtfl=letclass_type_declarationkwdfx=let{pci_params=ls;pci_name={txt;_};_}=xinppf"@[<2>%s %a%a%a@ =@ %a@]%a"kwdvirtual_flagx.pci_virt(class_params_defctxt)lsident_of_nametxt(class_typectxt)x.pci_expr(item_attributesctxt)x.pci_attributesinmatchlwith|[]->()|[x]->class_type_declaration"class type"fx|x::xs->ppf"@[<v>%a@,%a@]"(class_type_declaration"class type")x(list~sep:"@,"(class_type_declaration"and"))xsandclass_fieldctxtfx=matchx.pcf_descwith|Pcf_inherit(ovf,ce,so)->ppf"@[<2>inherit@ %s@ %a%a@]%a"(overrideovf)(class_exprctxt)ce(funfso->matchsowith|None->();|Some(s)->ppf"@ as %a"ident_of_names.txt)so(item_attributesctxt)x.pcf_attributes|Pcf_val(s,mf,Cfk_concrete(ovf,e))->ppf"@[<2>val%s %a%a =@;%a@]%a"(overrideovf)mutable_flagmfident_of_names.txt(expressionctxt)e(item_attributesctxt)x.pcf_attributes|Pcf_method(s,pf,Cfk_virtualct)->ppf"@[<2>method virtual %a %a :@;%a@]%a"private_flagpfident_of_names.txt(core_typectxt)ct(item_attributesctxt)x.pcf_attributes|Pcf_val(s,mf,Cfk_virtualct)->ppf"@[<2>val virtual %a%a :@ %a@]%a"mutable_flagmfident_of_names.txt(core_typectxt)ct(item_attributesctxt)x.pcf_attributes|Pcf_method(s,pf,Cfk_concrete(ovf,e))->letbinde=bindingctxtf{pvb_pat={ppat_desc=Ppat_vars;ppat_loc=Location.none;ppat_loc_stack=[];ppat_attributes=[]};pvb_expr=e;pvb_constraint=None;pvb_attributes=[];pvb_loc=Location.none;}inppf"@[<2>method%s %a%a@]%a"(overrideovf)private_flagpf(funf->function|{pexp_desc=Pexp_poly(e,Somect);pexp_attributes=[];_}->ppf"%a :@;%a=@;%a"ident_of_names.txt(core_typectxt)ct(expressionctxt)e|{pexp_desc=Pexp_poly(e,None);pexp_attributes=[];_}->binde|_->binde)e(item_attributesctxt)x.pcf_attributes|Pcf_constraint(ct1,ct2)->ppf"@[<2>constraint %a =@;%a@]%a"(core_typectxt)ct1(core_typectxt)ct2(item_attributesctxt)x.pcf_attributes|Pcf_initializer(e)->ppf"@[<2>initializer@ %a@]%a"(expressionctxt)e(item_attributesctxt)x.pcf_attributes|Pcf_attributea->floating_attributectxtfa|Pcf_extensione->item_extensionctxtfe;item_attributesctxtfx.pcf_attributesandclass_structurectxtf{pcstr_self=p;pcstr_fields=l}=ppf"@[<hv0>@[<hv2>object%a@;%a@]@;end@]"(funfp->matchp.ppat_descwith|Ppat_any->()|Ppat_constraint_->ppf" %a"(patternctxt)p|_->ppf" (%a)"(patternctxt)p)p(list(class_fieldctxt))landclass_exprctxtfx=ifx.pcl_attributes<>[]thenbeginppf"((%a)%a)"(class_exprctxt){xwithpcl_attributes=[]}(attributesctxt)x.pcl_attributesendelsematchx.pcl_descwith|Pcl_structure(cs)->class_structurectxtfcs|Pcl_fun(l,eo,p,e)->ppf"fun@ %a@ ->@ %a"(label_expctxt)(l,eo,p)(class_exprctxt)e|Pcl_let(rf,l,ce)->ppf"%a@ in@ %a"(bindingsctxt)(rf,l)(class_exprctxt)ce|Pcl_apply(ce,l)->ppf"((%a)@ %a)"(* Cf: #7200 *)(class_exprctxt)ce(list(label_x_expression_paramctxt))l|Pcl_constr(li,l)->ppf"%a%a"(funfl->ifl<>[]thenppf"[%a]@ "(list(core_typectxt)~sep:",")l)llongident_locli|Pcl_constraint(ce,ct)->ppf"(%a@ :@ %a)"(class_exprctxt)ce(class_typectxt)ct|Pcl_extensione->extensionctxtfe|Pcl_open(o,e)->ppf"@[<2>let open%s %a in@;%a@]"(overrideo.popen_override)longident_loco.popen_expr(class_exprctxt)eandmodule_typectxtfx=ifx.pmty_attributes<>[]thenbeginppf"((%a)%a)"(module_typectxt){xwithpmty_attributes=[]}(attributesctxt)x.pmty_attributesendelsematchx.pmty_descwith|Pmty_functor(Unit,mt2)->ppf"@[<hov2>() ->@ %a@]"(module_typectxt)mt2|Pmty_functor(Named(s,mt1),mt2)->beginmatchs.txtwith|None->ppf"@[<hov2>%a@ ->@ %a@]"(module_type1ctxt)mt1(module_typectxt)mt2|Somename->ppf"@[<hov2>functor@ (%s@ :@ %a)@ ->@ %a@]"name(module_typectxt)mt1(module_typectxt)mt2end|Pmty_with(mt,[])->module_typectxtfmt|Pmty_with(mt,l)->ppf"@[<hov2>%a@ with@ %a@]"(module_type1ctxt)mt(list(with_constraintctxt)~sep:"@ and@ ")l|_->module_type1ctxtfxandwith_constraintctxtf=function|Pwith_type(li,({ptype_params=ls;_}astd))->ppf"type@ %a %a =@ %a"(type_paramsctxt)lslongident_locli(type_declarationctxt)td|Pwith_module(li,li2)->ppf"module %a =@ %a"longident_loclilongident_locli2;|Pwith_modtype(li,mty)->ppf"module type %a =@ %a"longident_locli(module_typectxt)mty;|Pwith_typesubst(li,({ptype_params=ls;_}astd))->ppf"type@ %a %a :=@ %a"(type_paramsctxt)lslongident_locli(type_declarationctxt)td|Pwith_modsubst(li,li2)->ppf"module %a :=@ %a"longident_loclilongident_locli2|Pwith_modtypesubst(li,mty)->ppf"module type %a :=@ %a"longident_locli(module_typectxt)mty;andmodule_type1ctxtfx=ifx.pmty_attributes<>[]thenmodule_typectxtfxelsematchx.pmty_descwith|Pmty_identli->ppf"%a"longident_locli;|Pmty_aliasli->ppf"(module %a)"longident_locli;|Pmty_signature(s)->ppf"@[<hv0>@[<hv2>sig@ %a@]@ end@]"(* "@[<hov>sig@ %a@ end@]" *)(list(signature_itemctxt))s(* FIXME wrong indentation*)|Pmty_typeofme->ppf"@[<hov2>module@ type@ of@ %a@]"(module_exprctxt)me|Pmty_extensione->extensionctxtfe|_->parentrue(module_typectxt)fxandsignaturectxtfx=list~sep:"@\n"(signature_itemctxt)fxandsignature_itemctxtfx:unit=matchx.psig_descwith|Psig_type(rf,l)->type_def_listctxtf(rf,true,l)|Psig_typesubstl->(* Psig_typesubst is never recursive, but we specify [Recursive] here to
avoid printing a [nonrec] flag, which would be rejected by the parser.
*)type_def_listctxtf(Recursive,false,l)|Psig_valuevd->letintro=ifvd.pval_prim=[]then"val"else"external"inppf"@[<2>%s@ %a@ :@ %a@]%a"introident_of_namevd.pval_name.txt(value_descriptionctxt)vd(item_attributesctxt)vd.pval_attributes|Psig_typextte->type_extensionctxtfte|Psig_exceptioned->exception_declarationctxtfed|Psig_classl->letclass_descriptionkwdf({pci_params=ls;pci_name={txt;_};_}asx)=ppf"@[<2>%s %a%a%a@;:@;%a@]%a"kwdvirtual_flagx.pci_virt(class_params_defctxt)lsident_of_nametxt(class_typectxt)x.pci_expr(item_attributesctxt)x.pci_attributesinbeginmatchlwith|[]->()|[x]->class_description"class"fx|x::xs->ppf"@[<v>%a@,%a@]"(class_description"class")x(list~sep:"@,"(class_description"and"))xsend|Psig_module({pmd_type={pmty_desc=Pmty_aliasalias;pmty_attributes=[];_};_}aspmd)->ppf"@[<hov>module@ %s@ =@ %a@]%a"(Option.valuepmd.pmd_name.txt~default:"_")longident_localias(item_attributesctxt)pmd.pmd_attributes|Psig_modulepmd->ppf"@[<hov>module@ %s@ :@ %a@]%a"(Option.valuepmd.pmd_name.txt~default:"_")(module_typectxt)pmd.pmd_type(item_attributesctxt)pmd.pmd_attributes|Psig_modsubstpms->ppf"@[<hov>module@ %s@ :=@ %a@]%a"pms.pms_name.txtlongident_locpms.pms_manifest(item_attributesctxt)pms.pms_attributes|Psig_openod->ppf"@[<hov2>open%s@ %a@]%a"(overrideod.popen_override)longident_locod.popen_expr(item_attributesctxt)od.popen_attributes|Psig_includeincl->ppf"@[<hov2>include@ %a@]%a"(module_typectxt)incl.pincl_mod(item_attributesctxt)incl.pincl_attributes|Psig_modtype{pmtd_name=s;pmtd_type=md;pmtd_attributes=attrs}->ppf"@[<hov2>module@ type@ %s%a@]%a"s.txt(funfmd->matchmdwith|None->()|Somemt->pp_print_spacef();ppf"@ =@ %a"(module_typectxt)mt)md(item_attributesctxt)attrs|Psig_modtypesubst{pmtd_name=s;pmtd_type=md;pmtd_attributes=attrs}->letmd=matchmdwith|None->assertfalse(* ast invariant *)|Somemt->mtinppf"@[<hov2>module@ type@ %s@ :=@ %a@]%a"s.txt(module_typectxt)md(item_attributesctxt)attrs|Psig_class_type(l)->class_type_declaration_listctxtfl|Psig_recmoduledecls->letrecstring_x_module_type_listf?(first=true)l=matchlwith|[]->();|pmd::tl->ifnotfirstthenppf"@ @[<hov2>and@ %s:@ %a@]%a"(Option.valuepmd.pmd_name.txt~default:"_")(module_type1ctxt)pmd.pmd_type(item_attributesctxt)pmd.pmd_attributeselseppf"@[<hov2>module@ rec@ %s:@ %a@]%a"(Option.valuepmd.pmd_name.txt~default:"_")(module_type1ctxt)pmd.pmd_type(item_attributesctxt)pmd.pmd_attributes;string_x_module_type_listf~first:falsetlinstring_x_module_type_listfdecls|Psig_attributea->floating_attributectxtfa|Psig_extension(e,a)->item_extensionctxtfe;item_attributesctxtfaandmodule_exprctxtfx=ifx.pmod_attributes<>[]thenppf"((%a)%a)"(module_exprctxt){xwithpmod_attributes=[]}(attributesctxt)x.pmod_attributeselsematchx.pmod_descwith|Pmod_structure(s)->ppf"@[<hv2>struct@;@[<0>%a@]@;<1 -2>end@]"(list(structure_itemctxt)~sep:"@\n")s;|Pmod_constraint(me,mt)->ppf"@[<hov2>(%a@ :@ %a)@]"(module_exprctxt)me(module_typectxt)mt|Pmod_ident(li)->ppf"%a"longident_locli;|Pmod_functor(Unit,me)->ppf"functor ()@;->@;%a"(module_exprctxt)me|Pmod_functor(Named(s,mt),me)->ppf"functor@ (%s@ :@ %a)@;->@;%a"(Option.values.txt~default:"_")(module_typectxt)mt(module_exprctxt)me|Pmod_apply(me1,me2)->ppf"(%a)(%a)"(module_exprctxt)me1(module_exprctxt)me2(* Cf: #7200 *)|Pmod_apply_unitme1->ppf"(%a)()"(module_exprctxt)me1|Pmod_unpacke->ppf"(val@ %a)"(expressionctxt)e|Pmod_extension({txt;_},_)whentxt=Ast_helper.hole_txt->ppf"_"|Pmod_extensione->extensionctxtfeandstructurectxtfx=list~sep:"@\n"(structure_itemctxt)fxandpayloadctxtf=function|PStr[{pstr_desc=Pstr_eval(e,attrs)}]->ppf"@[<2>%a@]%a"(expressionctxt)e(item_attributesctxt)attrs|PStrx->structurectxtfx|PTypx->ppf":@ ";core_typectxtfx|PSigx->ppf":@ ";signaturectxtfx|PPat(x,None)->ppf"?";patternctxtfx|PPat(x,Somee)->ppf"?@ ";patternctxtfx;ppf" when ";expressionctxtfe(* transform [f = fun g h -> ..] to [f g h = ... ] could be improved *)andbindingctxtf{pvb_pat=p;pvb_expr=x;pvb_constraint=ct;_}=(* .pvb_attributes have already been printed by the caller, #bindings *)letrecpp_print_pexp_functionfx=ifx.pexp_attributes<>[]thenppf"=@;%a"(expressionctxt)xelsematchx.pexp_descwith|Pexp_function(params,c,body)->function_params_then_bodyctxtfparamscbody~delimiter:"="|Pexp_newtype(str,e)->ppf"(type@ %a)@ %a"ident_of_namestr.txtpp_print_pexp_functione|_->ppf"=@;%a"(expressionctxt)xinmatchctwith|Some(Pvc_constraint{locally_abstract_univars=[];typ})->ppf"%a@;:@;%a@;=@;%a"(simple_patternctxt)p(core_typectxt)typ(expressionctxt)x|Some(Pvc_constraint{locally_abstract_univars=vars;typ})->ppf"%a@;: type@;%a.@;%a@;=@;%a"(simple_patternctxt)p(listpp_print_string~sep:"@;")(List.map(funx->x.txt)vars)(core_typectxt)typ(expressionctxt)x|Some(Pvc_coercion{ground=None;coercion})->ppf"%a@;:>@;%a@;=@;%a"(simple_patternctxt)p(core_typectxt)coercion(expressionctxt)x|Some(Pvc_coercion{ground=Someground;coercion})->ppf"%a@;:%a@;:>@;%a@;=@;%a"(simple_patternctxt)p(core_typectxt)ground(core_typectxt)coercion(expressionctxt)x|None->beginmatchpwith|{ppat_desc=Ppat_var_;ppat_attributes=[]}->ppf"%a@ %a"(simple_patternctxt)ppp_print_pexp_functionx|_->ppf"%a@;=@;%a"(patternctxt)p(expressionctxt)xend(* [in] is not printed *)andbindingsctxtf(rf,l)=letbindingkwdrffx=ppf"@[<2>%s %a%a@]%a"kwdrec_flagrf(bindingctxt)x(item_attributesctxt)x.pvb_attributesinmatchlwith|[]->()|[x]->binding"let"rffx|x::xs->ppf"@[<v>%a@,%a@]"(binding"let"rf)x(list~sep:"@,"(binding"and"Nonrecursive))xsandbinding_opctxtfx=matchx.pbop_pat,x.pbop_expwith|{ppat_desc=Ppat_var{txt=pvar;_};ppat_attributes=[];_},{pexp_desc=Pexp_ident{txt=Lidentevar;_};pexp_attributes=[];_}whenpvar=evar->ppf"@[<2>%s %s@]"x.pbop_op.txtevar|pat,exp->ppf"@[<2>%s %a@;=@;%a@]"x.pbop_op.txt(patternctxt)pat(expressionctxt)expandstructure_itemctxtfx=matchx.pstr_descwith|Pstr_eval(e,attrs)->ppf"@[<hov2>;;%a@]%a"(expressionctxt)e(item_attributesctxt)attrs|Pstr_type(_,[])->assertfalse|Pstr_type(rf,l)->type_def_listctxtf(rf,true,l)|Pstr_value(rf,l)->(* pp f "@[<hov2>let %a%a@]" rec_flag rf bindings l *)ppf"@[<2>%a@]"(bindingsctxt)(rf,l)|Pstr_typextte->type_extensionctxtfte|Pstr_exceptioned->exception_declarationctxtfed|Pstr_modulex->letrecmodule_helper=function|{pmod_desc=Pmod_functor(arg_opt,me');pmod_attributes=[]}->beginmatcharg_optwith|Unit->ppf"()"|Named(s,mt)->ppf"(%s:%a)"(Option.values.txt~default:"_")(module_typectxt)mtend;module_helperme'|me->meinppf"@[<hov2>module %s%a@]%a"(Option.valuex.pmb_name.txt~default:"_")(funfme->letme=module_helpermeinmatchmewith|{pmod_desc=Pmod_constraint(me',({pmty_desc=(Pmty_ident(_)|Pmty_signature(_));_}asmt));pmod_attributes=[]}->ppf" :@;%a@;=@;%a@;"(module_typectxt)mt(module_exprctxt)me'|_->ppf" =@ %a"(module_exprctxt)me)x.pmb_expr(item_attributesctxt)x.pmb_attributes|Pstr_openod->ppf"@[<2>open%s@;%a@]%a"(overrideod.popen_override)(module_exprctxt)od.popen_expr(item_attributesctxt)od.popen_attributes|Pstr_modtype{pmtd_name=s;pmtd_type=md;pmtd_attributes=attrs}->ppf"@[<hov2>module@ type@ %s%a@]%a"s.txt(funfmd->matchmdwith|None->()|Somemt->pp_print_spacef();ppf"@ =@ %a"(module_typectxt)mt)md(item_attributesctxt)attrs|Pstr_classl->letextract_class_argscl=letrecloopacc=function|{pcl_desc=Pcl_fun(l,eo,p,cl');pcl_attributes=[]}->loop((l,eo,p)::acc)cl'|cl->List.revacc,clinletargs,cl=loop[]clinletconstr,cl=matchclwith|{pcl_desc=Pcl_constraint(cl',ct);pcl_attributes=[]}->Somect,cl'|_->None,clinargs,constr,clinletclass_constraintfct=ppf": @[%a@] "(class_typectxt)ctinletclass_declarationkwdf({pci_params=ls;pci_name={txt;_};_}asx)=letargs,constr,cl=extract_class_argsx.pci_exprinppf"@[<2>%s %a%a%a %a%a=@;%a@]%a"kwdvirtual_flagx.pci_virt(class_params_defctxt)lsident_of_nametxt(list(label_expctxt))args(optionclass_constraint)constr(class_exprctxt)cl(item_attributesctxt)x.pci_attributesinbeginmatchlwith|[]->()|[x]->class_declaration"class"fx|x::xs->ppf"@[<v>%a@,%a@]"(class_declaration"class")x(list~sep:"@,"(class_declaration"and"))xsend|Pstr_class_typel->class_type_declaration_listctxtfl|Pstr_primitivevd->ppf"@[<hov2>external@ %a@ :@ %a@]%a"ident_of_namevd.pval_name.txt(value_descriptionctxt)vd(item_attributesctxt)vd.pval_attributes|Pstr_includeincl->ppf"@[<hov2>include@ %a@]%a"(module_exprctxt)incl.pincl_mod(item_attributesctxt)incl.pincl_attributes|Pstr_recmoduledecls->(* 3.07 *)letauxf=function|({pmb_expr={pmod_desc=Pmod_constraint(expr,typ)}}aspmb)->ppf"@[<hov2>@ and@ %s:%a@ =@ %a@]%a"(Option.valuepmb.pmb_name.txt~default:"_")(module_typectxt)typ(module_exprctxt)expr(item_attributesctxt)pmb.pmb_attributes|pmb->ppf"@[<hov2>@ and@ %s@ =@ %a@]%a"(Option.valuepmb.pmb_name.txt~default:"_")(module_exprctxt)pmb.pmb_expr(item_attributesctxt)pmb.pmb_attributesinbeginmatchdeclswith|({pmb_expr={pmod_desc=Pmod_constraint(expr,typ)}}aspmb)::l2->ppf"@[<hv>@[<hov2>module@ rec@ %s:%a@ =@ %a@]%a@ %a@]"(Option.valuepmb.pmb_name.txt~default:"_")(module_typectxt)typ(module_exprctxt)expr(item_attributesctxt)pmb.pmb_attributes(funfl2->List.iter(auxf)l2)l2|pmb::l2->ppf"@[<hv>@[<hov2>module@ rec@ %s@ =@ %a@]%a@ %a@]"(Option.valuepmb.pmb_name.txt~default:"_")(module_exprctxt)pmb.pmb_expr(item_attributesctxt)pmb.pmb_attributes(funfl2->List.iter(auxf)l2)l2|_->assertfalseend|Pstr_attributea->floating_attributectxtfa|Pstr_extension(e,a)->item_extensionctxtfe;item_attributesctxtfaandtype_paramctxtf(ct,(a,b))=ppf"%s%s%a"(type_variancea)(type_injectivityb)(core_typectxt)ctandtype_paramsctxtf=function|[]->()|l->ppf"%a "(list(type_paramctxt)~first:"("~last:")"~sep:",@;")landtype_def_listctxtf(rf,exported,l)=lettype_declkwdrffx=leteq=if(x.ptype_kind=Ptype_abstract)&&(x.ptype_manifest=None)then""elseifexportedthen" ="else" :="inppf"@[<2>%s %a%a%a%s%a@]%a"kwdnonrec_flagrf(type_paramsctxt)x.ptype_paramsident_of_namex.ptype_name.txteq(type_declarationctxt)x(item_attributesctxt)x.ptype_attributesinmatchlwith|[]->assertfalse|[x]->type_decl"type"rffx|x::xs->ppf"@[<v>%a@,%a@]"(type_decl"type"rf)x(list~sep:"@,"(type_decl"and"Recursive))xsandrecord_declarationctxtflbls=lettype_record_fieldfpld=ppf"@[<2>%a%a:@;%a@;%a@]"mutable_flagpld.pld_mutableident_of_namepld.pld_name.txt(core_typectxt)pld.pld_type(attributesctxt)pld.pld_attributesinppf"{@\n%a}"(listtype_record_field~sep:";@\n")lblsandtype_declarationctxtfx=(* type_declaration has an attribute field,
but it's been printed by the caller of this method *)letprivf=matchx.ptype_privatewith|Public->()|Private->ppf"@;private"inletmanifestf=matchx.ptype_manifestwith|None->()|Somey->ifx.ptype_kind=Ptype_abstractthenppf"%t@;%a"priv(core_typectxt)yelseppf"@;%a"(core_typectxt)yinletconstructor_declarationfpcd=ppf"|@;";constructor_declarationctxtf(pcd.pcd_name.txt,pcd.pcd_vars,pcd.pcd_args,pcd.pcd_res,pcd.pcd_attributes)inletreprf=letintrof=ifx.ptype_manifest=Nonethen()elseppf"@;="inmatchx.ptype_kindwith|Ptype_variantxs->letvariantsfmtxs=ifxs=[]thenppfmt" |"elseppfmt"@\n%a"(list~sep:"@\n"constructor_declaration)xsinppf"%t%t%a"introprivvariantsxs|Ptype_abstract->()|Ptype_recordl->ppf"%t%t@;%a"intropriv(record_declarationctxt)l|Ptype_open->ppf"%t%t@;.."introprivinletconstraintsf=List.iter(fun(ct1,ct2,_)->ppf"@[<hov2>@ constraint@ %a@ =@ %a@]"(core_typectxt)ct1(core_typectxt)ct2)x.ptype_cstrsinppf"%t%t%t"manifestreprconstraintsandtype_extensionctxtfx=letextension_constructorfx=ppf"@\n|@;%a"(extension_constructorctxt)xinppf"@[<2>type %a%a += %a@ %a@]%a"(funf->function|[]->()|l->ppf"%a@;"(list(type_paramctxt)~first:"("~last:")"~sep:",")l)x.ptyext_paramslongident_locx.ptyext_pathprivate_flagx.ptyext_private(* Cf: #7200 *)(list~sep:""extension_constructor)x.ptyext_constructors(item_attributesctxt)x.ptyext_attributesandconstructor_declarationctxtf(name,vars,args,res,attrs)=letname=matchnamewith|"::"->"(::)"|s->sinletpp_varsfvs=matchvswith|[]->()|vs->ppf"%a@;.@;"(listtyvar_loc~sep:"@;")vsinmatchreswith|None->ppf"%s%a@;%a"name(funf->function|Pcstr_tuple[]->()|Pcstr_tuplel->ppf"@;of@;%a"(list(core_type1ctxt)~sep:"@;*@;")l|Pcstr_recordl->ppf"@;of@;%a"(record_declarationctxt)l)args(attributesctxt)attrs|Somer->ppf"%s:@;%a%a@;%a"namepp_varsvars(funf->function|Pcstr_tuple[]->core_type1ctxtfr|Pcstr_tuplel->ppf"%a@;->@;%a"(list(core_type1ctxt)~sep:"@;*@;")l(core_type1ctxt)r|Pcstr_recordl->ppf"%a@;->@;%a"(record_declarationctxt)l(core_type1ctxt)r)args(attributesctxt)attrsandextension_constructorctxtfx=(* Cf: #7200 *)matchx.pext_kindwith|Pext_decl(v,l,r)->constructor_declarationctxtf(x.pext_name.txt,v,l,r,x.pext_attributes)|Pext_rebindli->ppf"%s@;=@;%a%a"x.pext_name.txtlongident_locli(attributesctxt)x.pext_attributesandcase_listctxtfl:unit=letauxf{pc_lhs;pc_guard;pc_rhs}=ppf"@;| @[<2>%a%a@;->@;%a@]"(patternctxt)pc_lhs(option(expressionctxt)~first:"@;when@;")pc_guard(expression(under_pipectxt))pc_rhsinlistauxfl~sep:""andlabel_x_expression_paramctxtf(l,e)=letsimple_name=matchewith|{pexp_desc=Pexp_ident{txt=Lidentl;_};pexp_attributes=[]}->Somel|_->Noneinmatchlwith|Nolabel->expression2ctxtfe(* level 2*)|Optionalstr->ifSomestr=simple_namethenppf"?%a"ident_of_namestrelseppf"?%a:%a"ident_of_namestr(simple_exprctxt)e|Labelledlbl->ifSomelbl=simple_namethenppf"~%a"ident_of_namelblelseppf"~%a:%a"ident_of_namelbl(simple_exprctxt)eanddirective_argumentfx=matchx.pdira_descwith|Pdir_string(s)->ppf"@ %S"s|Pdir_int(n,None)->ppf"@ %s"n|Pdir_int(n,Somem)->ppf"@ %s%c"nm|Pdir_ident(li)->ppf"@ %a"longidentli|Pdir_bool(b)->ppf"@ %s"(string_of_boolb)lettoplevel_phrasefx=matchxwith|Ptop_def(s)->ppf"@[<hov0>%a@]"(list(structure_itemreset_ctxt))s(* pp_open_hvbox f 0; *)(* pp_print_list structure_item f s ; *)(* pp_close_box f (); *)|Ptop_dir{pdir_name;pdir_arg=None;_}->ppf"@[<hov2>#%s@]"pdir_name.txt|Ptop_dir{pdir_name;pdir_arg=Somepdir_arg;_}->ppf"@[<hov2>#%s@ %a@]"pdir_name.txtdirective_argumentpdir_argletexpressionfx=ppf"@[%a@]"(expressionreset_ctxt)xletstring_of_expressionx=ignore(flush_str_formatter());letf=str_formatterinexpressionfx;flush_str_formatter()letstring_of_structurex=ignore(flush_str_formatter());letf=str_formatterinstructurereset_ctxtfx;flush_str_formatter()lettop_phrasefx=pp_print_newlinef();toplevel_phrasefx;ppf";;";pp_print_newlinef()letcore_type=core_typereset_ctxtletpattern=patternreset_ctxtletsignature=signaturereset_ctxtletstructure=structurereset_ctxtletmodule_expr=module_exprreset_ctxtletmodule_type=module_typereset_ctxtletclass_field=class_fieldreset_ctxtletclass_type_field=class_type_fieldreset_ctxtletclass_expr=class_exprreset_ctxtletclass_type=class_typereset_ctxtletstructure_item=structure_itemreset_ctxtletsignature_item=signature_itemreset_ctxtletbinding=bindingreset_ctxtletpayload=payloadreset_ctxtletcase_list=case_listreset_ctxtmoduleStyle=Misc.Style(* merlin: moved from parse.ml *)letprepare_errorerr=letsource=Location.ParserinletopenSyntaxerrinmatcherrwith|Unclosed(opening_loc,opening,closing_loc,closing)->Location.errorf~source~loc:closing_loc~sub:[Location.msg~loc:opening_loc"This %a might be unmatched"Style.inline_codeopening]"Syntax error: %a expected"Style.inline_codeclosing|Expecting(loc,nonterm)->Location.errorf~source~loc"Syntax error: %a expected."Style.inline_codenonterm|Not_expecting(loc,nonterm)->Location.errorf~source~loc"Syntax error: %a not expected."Style.inline_codenonterm|Applicative_pathloc->Location.errorf~source~loc"Syntax error: applicative paths of the form %a \
are not supported when the option %a is set."Style.inline_code"F(X).t"Style.inline_code"-no-app-func"|Variable_in_scope(loc,var)->Location.errorf~source~loc"In this scoped type, variable %a \
is reserved for the local type %a."(Style.as_inline_codetyvar)varStyle.inline_codevar|Otherloc->Location.errorf~source~loc"Syntax error"|Ill_formed_ast(loc,s)->Location.errorf~source~loc"broken invariant in parsetree: %s"s|Invalid_package_type(loc,ipt)->letinvalidppfipt=matchiptwith|Syntaxerr.Parameterized_types->Format.fprintfppf"parametrized types are not supported"|Constrained_types->Format.fprintfppf"constrained types are not supported"|Private_types->Format.fprintfppf"private types are not supported"|Not_with_type->Format.fprintfppf"only %a constraints are supported"Style.inline_code"with type t ="|Neither_identifier_nor_with_type->Format.fprintfppf"only module type identifier and %a constraints are supported"Style.inline_code"with type"inLocation.errorf~source~loc"invalid package type: %a"invalidipt|Removed_string_setloc->Location.errorf~source~loc"Syntax error: strings are immutable, there is no assignment \
syntax for them.\n\
@{<hint>Hint@}: Mutable sequences of bytes are available in \
the Bytes module.\n\
@{<hint>Hint@}: Did you mean to use %a?"Style.inline_code"Bytes.set"let()=Location.register_error_of_exn(function|Syntaxerr.Errorerr->Some(prepare_errorerr)|_->None)