123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736openImportmoduleNon_intersecting_ranges:sigtypetvalempty:tvalinsert:node_name:string->Location.t->t->tvalunion:t->t->tvalcovered_by:t->loc:Location.t->bool(** [covered_by t ~loc = true] iff [t] is covered by [loc] *)valfind_outside:Location.t->t->string*Location.tend=structtypet={min_pos:Lexing.positionoption;max_pos:Lexing.positionoption;ranges:(string*Location.t)list;}letempty={min_pos=None;max_pos=None;ranges=[]}letrecinsertranges((node_name,node_loc)asnode)=matchrangeswith|[]->[node]|((x_name,x_loc)asx)::xs->letopenLocationinifcompare_posnode_loc.loc_startx_loc.loc_end>=0thennode::x::xselseifcompare_posx_loc.loc_startnode_loc.loc_end>=0thenx::insertxsnodeelseraise_errorf~loc:node_loc"invalid output from ppx, %s overlaps with %s at location:@.%a"node_namex_nameLocation.printx_locletmin_posp1p2=match(p1,p2)with|None,None->None|(Some_asp),None|None,(Some_asp)->p|Somep1,Somep2->Some(Location.min_posp1p2)letmax_posp1p2=match(p1,p2)with|None,None->None|(Some_asp),None|None,(Some_asp)->p|Somep1,Somep2->Some(Location.max_posp1p2)letlongest_firstl1l2~stop_after=letrecloopxsysn=match(xs,ys,n)with|[],_,_|_,_,0->(l2,l1)|_,[],_->(l1,l2)|_::xs,_::ys,n->loopxsys(n-1)inloopl1l2stop_afterletuniont1t2=letinit,l=longest_firstt1.rangest2.ranges~stop_after:42inletranges=List.fold_leftl~init~f:insertin{min_pos=min_post1.min_post2.min_pos;max_pos=max_post1.max_post2.max_pos;ranges;}letinsert~node_nameloct={min_pos=min_pos(Someloc.loc_start)t.min_pos;max_pos=max_pos(Someloc.loc_end)t.max_pos;ranges=insertt.ranges(node_name,loc);}letcovered_byt~loc=match(t.min_pos,t.max_pos)with|None,None->true|Somemin_pos,Somemax_pos->Location.compare_posmin_posloc.loc_start>=0&&Location.compare_posmax_posloc.loc_end<=0|_,_->(* there are no open ranges *)assertfalseletfind_outsideloct=List.findt.ranges~f:(fun(_,l)->Location.compare_posloc.loc_startl.loc_start>0||Location.compare_posloc.loc_endl.loc_end<0)endletreloc_pmty_functorsx=letoutmost_loc=x.pmty_locinletrecauxx=matchx.pmty_descwith|Pmty_functor(Unit,initial_res)->letres=auxinitial_resinifres==initial_resthenxelse{xwithpmty_desc=Pmty_functor(Unit,res)}|Pmty_functor(Named(id,mty),initial_res)->letres=auxinitial_resinifLocation.compareoutmost_locres.pmty_loc=0thenletloc_start=mty.pmty_loc.loc_endinletres={reswithpmty_loc={res.pmty_locwithloc_start}}in{xwithpmty_desc=Pmty_functor(Named(id,mty),res)}elseifres==initial_resthenxelse{xwithpmty_desc=Pmty_functor(Named(id,mty),res)}|_->xinauxxletreloc_pmod_functorsx=letoutmost_loc=x.pmod_locinletrecauxx=matchx.pmod_descwith|Pmod_functor(Unit,initial_res)->letres=auxinitial_resinifres==initial_resthenxelse{xwithpmod_desc=Pmod_functor(Unit,res)}|Pmod_functor(Named(id,mty),initial_res)->letres=auxinitial_resinifLocation.compareoutmost_locres.pmod_loc=0thenletloc_start=mty.pmty_loc.loc_endinletres={reswithpmod_loc={res.pmod_locwithloc_start}}in{xwithpmod_desc=Pmod_functor(Named(id,mty),res)}elseifres==initial_resthenxelse{xwithpmod_desc=Pmod_functor(Named(id,mty),res)}|_->xinauxxletall_payloads_inside_parent~loc=List.for_all~f:(funattr->Location.compare_posloc.loc_endattr.attr_loc.loc_end>=0)letfile:stringoptionref=refNoneletsame_file_so_far=reftrueletstayed_in_the_same_filefname=(* TODO: remove uses of Location.none from the ppxes. *)ifString.equalfname"_none_"thentrue(* do nothing for now. *)elsematch!filewith|None->file:=Somefname;true|Someorig_fname->String.equalorig_fnamefname||(same_file_so_far:=false;false)letshould_ignorelocattrs=(* If the filename changed, then there were line directives, and the locations
are all messed up. *)(not(stayed_in_the_same_fileloc.loc_start.pos_fname))||(* Ignore things explicitly marked. *)List.exists~f:(funattr->String.equalattr.attr_name.txtMerlin_helpers.hide_attribute.attr_name.txt)attrsletrecextract_constrainte=matche.pexp_descwith|Pexp_constraint(e,ct)|Pexp_coerce(e,_,ct)->Some(e,ct)|Pexp_newtype(name,exp)->Option.map(extract_constraintexp)~f:(fun(exp,ct)->({ewithpexp_desc=Pexp_newtype(name,exp);pexp_loc={e.pexp_locwithloc_ghost=true};},ct))|_->Noneletdo_check~node_namenode_locchildrens_locssiblings_locs=ifnot!same_file_so_farthenNon_intersecting_ranges.emptyelseifnode_loc.loc_ghostthenNon_intersecting_ranges.unionchildrens_locssiblings_locselseifNon_intersecting_ranges.covered_bychildrens_locs~loc:node_locthenNon_intersecting_ranges.insert~node_namenode_locsiblings_locselseletchild_name,child_loc=Non_intersecting_ranges.find_outsidenode_locchildrens_locsinLocation.raise_errorf~loc:node_loc"invalid output from ppx:@ this %s is built from a%s whose location is \
outside of this node's.@.Child %s found at:@ %a"node_name((matchString.unsafe_getchild_name0with|'a'|'e'|'i'|'o'|'u'->"n "|_->" ")^child_name)child_nameLocation.printchild_locletenforce_invariantsfname=let()=file:=fnameinobject(self)inherit[Non_intersecting_ranges.t]Ast_traverse.foldassuper(* TODO: we should generate a class which enforces the location invariant.
And then we should only override the methods where we need an escape
hatch because the parser isn't doing the right thing.
That would ensure that we stay up to date as the AST changes. *)method!longident_locxsiblings=ifx.loc.loc_ghostthensiblingselseNon_intersecting_ranges.insert~node_name:"ident"x.locsiblingsmethod!row_fieldxsiblings_locs=ifshould_ignorex.prf_locx.prf_attributesthensiblings_locselseletchildrens_locs=super#row_fieldxNon_intersecting_ranges.emptyindo_check~node_name:"row field"x.prf_locchildrens_locssiblings_locsmethod!object_fieldxsiblings_locs=ifshould_ignorex.pof_locx.pof_attributesthensiblings_locselseletchildrens_locs=super#object_fieldxNon_intersecting_ranges.emptyindo_check~node_name:"object field"x.pof_locchildrens_locssiblings_locsmethod!binding_opxsiblings_locs=letchildrens_locs=super#binding_opxNon_intersecting_ranges.emptyindo_check~node_name:"binding operator"x.pbop_locchildrens_locssiblings_locsmethod!value_descriptionxsiblings_locs=ifshould_ignorex.pval_locx.pval_attributesthensiblings_locselseletchildrens_locs=super#value_descriptionxNon_intersecting_ranges.emptyindo_check~node_name:"value description"x.pval_locchildrens_locssiblings_locsmethod!type_declarationxsiblings_locs=ifshould_ignorex.ptype_locx.ptype_attributesthensiblings_locselseletchildrens_locs=super#type_declarationxNon_intersecting_ranges.emptyindo_check~node_name:"type declaration"x.ptype_locchildrens_locssiblings_locsmethod!label_declarationxsiblings_locs=ifshould_ignorex.pld_locx.pld_attributesthensiblings_locselseletchildrens_locs=super#label_declarationxNon_intersecting_ranges.emptyindo_check~node_name:"label declaration"x.pld_locchildrens_locssiblings_locsmethod!constructor_declarationxsiblings_locs=ifshould_ignorex.pcd_locx.pcd_attributesthensiblings_locselseletchildrens_locs=super#constructor_declarationxNon_intersecting_ranges.emptyindo_check~node_name:"constructor declaration"x.pcd_locchildrens_locssiblings_locsmethod!type_extensionxsiblings_locs=ifshould_ignorex.ptyext_locx.ptyext_attributesthensiblings_locselseletchildrens_locs=super#type_extensionxNon_intersecting_ranges.emptyindo_check~node_name:"type extension"x.ptyext_locchildrens_locssiblings_locsmethod!extension_constructorxsiblings_locs=ifshould_ignorex.pext_locx.pext_attributesthensiblings_locselseletchildrens_locs=super#extension_constructorxNon_intersecting_ranges.emptyindo_check~node_name:"extension constructor"x.pext_locchildrens_locssiblings_locsmethod!class_typexsiblings_locs=ifshould_ignorex.pcty_locx.pcty_attributesthensiblings_locselseletchildrens_locs=super#class_typexNon_intersecting_ranges.emptyindo_check~node_name:"class type"x.pcty_locchildrens_locssiblings_locsmethod!class_type_fieldxsiblings_locs=ifshould_ignorex.pctf_locx.pctf_attributesthensiblings_locselseletchildrens_locs=super#class_type_fieldxNon_intersecting_ranges.emptyindo_check~node_name:"class type field"x.pctf_locchildrens_locssiblings_locsmethod!class_infosfxsiblings_locs=ifshould_ignorex.pci_locx.pci_attributesthensiblings_locselseletchildrens_locs=super#class_infosfxNon_intersecting_ranges.emptyindo_check~node_name:"class"x.pci_locchildrens_locssiblings_locsmethod!class_exprxsiblings_locs=ifshould_ignorex.pcl_locx.pcl_attributesthensiblings_locselseletchildrens_locs=super#class_exprxNon_intersecting_ranges.emptyindo_check~node_name:"class expression"x.pcl_locchildrens_locssiblings_locsmethod!class_fieldxsiblings_locs=ifshould_ignorex.pcf_locx.pcf_attributesthensiblings_locselseletchildrens_locs=super#class_fieldxNon_intersecting_ranges.emptyindo_check~node_name:"class field"x.pcf_locchildrens_locssiblings_locsmethod!signature_itemxsiblings_locs=ifshould_ignorex.psig_loc[]thensiblings_locselseletchildrens_locs=super#signature_itemxNon_intersecting_ranges.emptyindo_check~node_name:"signature item"x.psig_locchildrens_locssiblings_locsmethod!module_declarationxsiblings_locs=ifshould_ignorex.pmd_locx.pmd_attributesthensiblings_locselseletchildrens_locs=super#module_declarationxNon_intersecting_ranges.emptyindo_check~node_name:"module declaration"x.pmd_locchildrens_locssiblings_locsmethod!module_substitutionxsiblings_locs=ifshould_ignorex.pms_locx.pms_attributesthensiblings_locselseletchildrens_locs=super#module_substitutionxNon_intersecting_ranges.emptyindo_check~node_name:"module substitution"x.pms_locchildrens_locssiblings_locsmethod!module_type_declarationxsiblings_locs=ifshould_ignorex.pmtd_locx.pmtd_attributesthensiblings_locselseletchildrens_locs=super#module_type_declarationxNon_intersecting_ranges.emptyindo_check~node_name:"module type declaration"x.pmtd_locchildrens_locssiblings_locsmethod!open_infosfxsiblings_locs=ifshould_ignorex.popen_locx.popen_attributesthensiblings_locselseletchildrens_locs=super#open_infosfxNon_intersecting_ranges.emptyindo_check~node_name:"open"x.popen_locchildrens_locssiblings_locsmethod!include_infosfxsiblings_locs=ifshould_ignorex.pincl_locx.pincl_attributesthensiblings_locselseletchildrens_locs=super#include_infosfxNon_intersecting_ranges.emptyindo_check~node_name:"include"x.pincl_locchildrens_locssiblings_locsmethod!structure_itemxsiblings_locs=ifshould_ignorex.pstr_loc[]thensiblings_locselseletchildrens_locs=super#structure_itemxNon_intersecting_ranges.emptyindo_check~node_name:"structure item"x.pstr_locchildrens_locssiblings_locsmethod!module_bindingxsiblings_locs=ifshould_ignorex.pmb_locx.pmb_attributesthensiblings_locselseletchildrens_locs=super#module_bindingxNon_intersecting_ranges.emptyindo_check~node_name:"module binding"x.pmb_locchildrens_locssiblings_locs(******************************************)(* The following is special cased because *)(* the type constraint is duplicated. *)(******************************************)method!value_bindingxsiblings_locs=ifshould_ignorex.pvb_locx.pvb_attributesthensiblings_locselseletchildrens_locs=match(x.pvb_pat.ppat_desc,extract_constraintx.pvb_expr)with(* let x : type a b c. ct = e *)|(Ppat_constraint(pvb_pat,{ptyp_desc=Ptyp_poly(_::_,ctp);_}),Some(pvb_expr,cte))(* let x : ct = e
let x :> ct = e *)|(Ppat_constraint(pvb_pat,{ptyp_desc=Ptyp_poly([],ctp);_}),Some(pvb_expr,cte))whenLocation.comparectp.ptyp_loccte.ptyp_loc=0->letacc=Non_intersecting_ranges.emptyinletacc=self#patternpvb_pataccinlet_acc=self#core_typectpaccinletacc=self#expressionpvb_expraccinletacc=self#attributesx.pvb_attributesaccinacc|_->super#value_bindingxNon_intersecting_ranges.emptyindo_check~node_name:"value binding"x.pvb_locchildrens_locssiblings_locs(**********************************************)(* The following is special cased because of: *)(* MT [@attr payload] *)(* where the loc of payload is outside the *)(* loc of the module type.... *)(* and *)(* functor (A : S) (B : S) ... *)(* where the loc of [(B : S) ...] is the same *)(* as the loc of the outermost module type. *)(**********************************************)method!module_typexsiblings_locs=ifshould_ignorex.pmty_locx.pmty_attributesthensiblings_locselseletx=reloc_pmty_functorsxinletchildrens_locs=ifall_payloads_inside_parent~loc:x.pmty_locx.pmty_attributesthensuper#module_typexNon_intersecting_ranges.emptyelseletacc=self#module_type_descx.pmty_descNon_intersecting_ranges.emptyinlet_=self#attributesx.pmty_attributesaccinaccindo_check~node_name:"module type"x.pmty_locchildrens_locssiblings_locs(**********************************************)(* The following is special cased because of: *)(* ME [@attr payload] *)(* where the loc of payload is outside the *)(* loc of the module expr.... *)(* and *)(* functor (A : S) (B : S) ... *)(* where the loc of [(B : S) ...] is the same *)(* as the loc of the outermost module expr. *)(**********************************************)method!module_exprxsiblings_locs=ifshould_ignorex.pmod_locx.pmod_attributesthensiblings_locselseletx=reloc_pmod_functorsxinletchildrens_locs=ifall_payloads_inside_parent~loc:x.pmod_locx.pmod_attributesthensuper#module_exprxNon_intersecting_ranges.emptyelseletacc=self#module_expr_descx.pmod_descNon_intersecting_ranges.emptyinlet_=self#attributesx.pmod_attributesaccinaccindo_check~node_name:"module expression"x.pmod_locchildrens_locssiblings_locs(*********************)(* Same as above ... *)(*********************)method!core_typexsiblings_locs=ifshould_ignorex.ptyp_locx.ptyp_attributesthensiblings_locselseletchildrens_locs=ifall_payloads_inside_parent~loc:x.ptyp_locx.ptyp_attributesthensuper#core_typexNon_intersecting_ranges.emptyelseletacc=self#core_type_descx.ptyp_descNon_intersecting_ranges.emptyinlet_=self#attributesx.ptyp_attributesaccinaccindo_check~node_name:"core type"x.ptyp_locchildrens_locssiblings_locs(*****************)(* And again ... *)(*****************)method!expressionxsiblings_locs=ifshould_ignorex.pexp_locx.pexp_attributesthensiblings_locselseletchildrens_locs=ifall_payloads_inside_parent~loc:x.pexp_locx.pexp_attributesthensuper#expressionxNon_intersecting_ranges.emptyelseletacc=self#expression_descx.pexp_descNon_intersecting_ranges.emptyinlet_=self#attributesx.pexp_attributesaccinaccindo_check~node_name:"expression"x.pexp_locchildrens_locssiblings_locs(*****************)(* ... and again *)(*****************)method!patternxsiblings_locs=ifshould_ignorex.ppat_locx.ppat_attributesthensiblings_locselseletchildrens_locs=ifall_payloads_inside_parent~loc:x.ppat_locx.ppat_attributesthensuper#patternxNon_intersecting_ranges.emptyelseletacc=self#pattern_descx.ppat_descNon_intersecting_ranges.emptyinlet_=self#attributesx.ppat_attributesaccinaccindo_check~node_name:"pattern"x.ppat_locchildrens_locssiblings_locs(***********************************************************)(* The following is special cased because the location of *)(* the construct equals the location of the type_exception *)(* (and so covers the location of the attributes). *)(***********************************************************)method!type_exceptionxsiblings_locs=ifshould_ignorex.ptyexn_locx.ptyexn_attributesthensiblings_locselseletinit=Non_intersecting_ranges.emptyinletchilds_locs=self#extension_constructorx.ptyexn_constructorinitinletattrs_locs=self#attributesx.ptyexn_attributesinitinignore(do_check~node_name:"exception"x.ptyexn_locattrs_locssiblings_locs);do_check~node_name:"exception"x.ptyexn_locchilds_locssiblings_locs(*******************************************)(* The following is overridden because the *)(* lhs is sometimes included in the rhs. *)(*******************************************)method!with_constraintxsiblings_loc=matchxwith|Pwith_type(_,tdecl)|Pwith_typesubst(_,tdecl)->self#type_declarationtdeclsiblings_loc|_->super#with_constraintxsiblings_loc(******************************************)(* The following is overridden because of:*)(* - Foo.{ bar; ... } *)(* - Foo.[ bar; ... ] *)(* - Foo.( bar; ... ) *)(* - method x : type a. ... = ... *)(* - foo.@(bar) *)(* - foo.@(bar) <- baz *)(* - foo.%.{bar} *)(* - foo.%.{bar} <- baz *)(* - foo.%.[bar] *)(* - foo.%.[bar] <- baz *)(******************************************)method!expression_descxacc=matchxwith|Pexp_record(labels,expr_o)->letacc=self#list(fun(lid,e)acc->ifLocation.compare_poslid.loc.loc_starte.pexp_loc.loc_start=0thenifLocation.comparelid.loce.pexp_loc=0then(* punning. *)self#longident_loclidaccelsematche.pexp_descwith|Pexp_constraint(e,c)->(* { foo : int } and { foo : int = x } ... *)let_=self#core_typecaccinself#expressioneacc|_->(* No idea what's going on there. *)self#expressioneaccelseletacc=self#longident_loclidaccinletacc=self#expressioneaccinacc)labelsaccinself#optionself#expressionexpr_oacc|Pexp_open(({popen_expr={pmod_desc=Pmod_identlid;_};_}asopn),e)whenLocation.compare_poslid.loc.loc_starte.pexp_loc.loc_start=0&&Location.compare_poslid.loc.loc_ende.pexp_loc.loc_end<>0->(* let's relocate ... *)lete_loc={e.pexp_locwithloc_start=lid.loc.loc_end}insuper#expression_desc(Pexp_open(opn,{ewithpexp_loc=e_loc}))acc|Pexp_poly(e,Some{ptyp_desc=Ptyp_poly(_,ct);_})->(matchextract_constraintewith|Some(e,cte)whenLocation.comparecte.ptyp_locct.ptyp_loc=0->letacc=self#expressioneaccinletacc=self#core_typectaccinacc|_->super#expression_descxacc)|Pexp_apply({pexp_desc=Pexp_ident{txt=lid;_};_},args)->(matchLongident.last_exnlidwith|idwhenString.is_prefixid~prefix:"."&&(String.is_suffixid~suffix:"()"||String.is_suffixid~suffix:"()<-"||String.is_suffixid~suffix:"[]"||String.is_suffixid~suffix:"[]<-"||String.is_suffixid~suffix:"{}"||String.is_suffixid~suffix:"{}<-")->self#list(fun(_,e)->self#expressione)argsacc|exception_->super#expression_descxacc|_->super#expression_descxacc)|_->super#expression_descxacc(*******************************************************)(* The following is overridden because of: *)(* - punning. *)(* - record field with type constraint. *)(* - unpack locations being incorrect when constrained *)(*******************************************************)method!pattern_descxacc=matchxwith|Ppat_record(labels,_)->self#list(fun(lid,pat)acc->ifLocation.compare_poslid.loc.loc_startpat.ppat_loc.loc_start=0thenifLocation.comparelid.locpat.ppat_loc=0then(* simple punning! *)self#longident_loclidaccelsematchpat.ppat_descwith|Ppat_constraint(p,c)->(* { foo : int } and { foo : int = x } ... *)let_=self#core_typecaccinself#patternpacc|_->(* No idea what's going on there. *)self#patternpataccelseletacc=self#longident_loclidaccinletacc=self#patternpataccinacc)labelsacc|Ppat_constraint({ppat_desc=Ppat_unpacka;_},b)->letacc=self#loc(self#optionself#string)aaccinself#core_typebacc|_->super#pattern_descxacc(***********************************************************)(* The following is overridden because the location of the *)(* fake structure for a generative argument covers the *)(* location of the functor. *)(***********************************************************)method!module_expr_descxacc=matchxwith|Pmod_apply(m,{pmod_desc=Pmod_structure[];pmod_loc;_})whenLocation.compare_posm.pmod_loc.loc_startpmod_loc.loc_start=0->super#module_exprmacc|_->super#module_expr_descxacc(***********************************************************)(* The following is overridden because the location of the *)(* open_infos for Pcl_open only covers the "open" keyword *)(* and not the module opened. *)(***********************************************************)method!class_expr_descxacc=matchxwith|Pcl_open(od,ce)->(* inline of open_description (which effectively makes that node
disappear) *)letacc=self#longident_locod.popen_expraccinletacc=self#override_flagod.popen_overrideaccinletacc=self#locationod.popen_locaccinletacc=self#attributesod.popen_attributesaccin(* continue *)letacc=self#class_exprceaccinacc|_->super#class_expr_descxacc(*********************)(* Same as above ... *)(*********************)method!class_type_descxacc=matchxwith|Pcty_open(od,ct)->(* inline of open_description (which effectively makes that node
disappear) *)letacc=self#longident_locod.popen_expraccinletacc=self#override_flagod.popen_overrideaccinletacc=self#locationod.popen_locaccinletacc=self#attributesod.popen_attributesaccin(* continue *)letacc=self#class_typectaccinacc|_->super#class_type_descxacc(**********************************************************)(* The following is overridden because docstrings have *)(* the same location as the item they get attached to. *)(**********************************************************)method!attributexacc=matchx.attr_name.txtwith|"ocaml.doc"|"ocaml.text"->acc|_->super#attributexaccend