Legend:
Page
Library
Module
Module type
Parameter
Class
Class type
Source
Source file VisitorsGeneration.ml
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586openLongidentletmknoloc=Location.mknolocopenAsttypesopenParsetreeopenAst_helperopenAst_convenienceopenVisitorsListopenVisitorsAnalysisopenVisitorsCompatibility(* This module offers helper functions for code generation. *)(* -------------------------------------------------------------------------- *)(* Type abbreviations. *)typevariable=stringtypedatacon=stringtypelabel=stringtypeclasse=stringtypemethode=stringtypetyvar=stringtypevariables=variablelisttypetyvars=tyvarlisttypecore_types=core_typelisttypepatterns=patternlisttypeexpressions=expressionlist(* -------------------------------------------------------------------------- *)(* We should in principle ensure that our code makes sense even if the
standard names that we rely upon are shadowed by the user. *)(* This is made slightly difficult by the fact that the name [Pervasives]
has been deprecated in favor of [Stdlib] in OCaml 4.07. *)(* One viable approach would be to define the names that we need in the
library [VisitorsRuntime], then refer to this library in the generated
code. *)(* One problem is that defining an alias for the standard operator (&&)
causes it to become strict instead of lazy! So we cannot define an
alias for it. *)(* Let's just cross our fingers and assume that the user won't shadow
the standard names that we need. *)letpervasive(x:string):Longident.t=Lidentx(* We normally place an improbable prefix in front of our private (local)
variables, so as to make sure that we do not shadow user variables that
are used in [@build] code fragments. *)(* When producing code for inclusion in the documentation, we remove this
prefix, just so that things look pretty. We rely on an undocumented
environment variable to toggle this behavior. *)letimprobable(x:string):string=trylet_=Sys.getenv"VISITORS_BUILDING_DOCUMENTATION"inxwithNot_found->"_visitors_"^x(* -------------------------------------------------------------------------- *)(* Types. *)letty_var(alpha:tyvar):core_type=Typ.varalphaletty_vars(alphas:tyvars):core_types=List.mapty_varalphasletty_any=Typ.any()letty_unit=tconstr"unit"[](* For [ty_arrow], see [VisitorsCompatibility]. *)letty_arrows:core_types->core_type->core_type=List.fold_rightty_arrow(* [decl_type decl] turns a declaration of the type ['a foo] into a the type
['a foo]. *)letdecl_type(decl:type_declaration):core_type=tconstrdecl.ptype_name.txt(ty_vars(decl_paramsdecl))(* -------------------------------------------------------------------------- *)(* [unit] produces a unit constant. [tuple] produces a tuple. [record]
produces a record. These functions already exist; we redefine them without
any optional arguments so as avoid OCaml's warning 48 (implicit elimination
of optional arguments). *)letunit()=unit()lettuplees=tupleesletrecordles=recordles(* -------------------------------------------------------------------------- *)(* [number i thing] constructs an English description of "[i] thing(s)". *)letnumberis=matchiwith|0->Printf.sprintf"zero %s"s|1->Printf.sprintf"one %s"s|_->Printf.sprintf"%d %ss"is(* -------------------------------------------------------------------------- *)(* [eident] converts a (possibly-qualified) identifier to an expression. *)leteident(id:Longident.t):expression=Exp.ident(mknolocid)(* -------------------------------------------------------------------------- *)(* [pvars] converts a list of variables to a list of patterns. *)letpvars(xs:variables):patterns=List.map(funx->pvarx)xs(* [evars] converts a list of variables to a list of expressions. *)letevars(xs:variables):expressions=List.map(funx->evarx)xs(* [pvarss] converts a matrix of variables to a matrix of patterns. *)letpvarss(xss:variableslist):patternslist=List.mappvarsxss(* [evarss] converts a matrix of variables to a matrix of expressions. *)letevarss(xss:variableslist):expressionslist=List.mapevarsxss(* -------------------------------------------------------------------------- *)(* [wildcards] converts a list of anything to a list of wildcard patterns. *)letwildcardsxs=List.map(fun_->Pat.any())xs(* -------------------------------------------------------------------------- *)(* [plambda p e] constructs a function [fun p -> e]. *)(* For [plambda], see [VisitorsCompatibility]. *)(* [lambda x e] constructs a function [fun x -> e]. *)letlambda(x:variable)(e:expression):expression=plambda(pvarx)e(* [plambdas ps e] constructs a multi-argument function [fun ps -> e]. *)letplambdas(ps:patterns)(e:expression):expression=List.fold_rightplambdapse(* [lambdas xs e] constructs a multi-argument function [fun xs -> e]. *)letlambdas(xs:variables)(e:expression):expression=List.fold_rightlambdaxse(* -------------------------------------------------------------------------- *)(* [app] works like [Ast_convenience.app] (which it shadows), except it avoids
constructing nested applications of the form [(f x) y], transforming them
instead into a single application [f x y]. The difference is probably just
cosmetic. *)letapp(e:expression)(es2:expressions):expression=matche.pexp_descwith|Pexp_apply(e1,les1)->letles2=List.map(fune->Label.nolabel,e)es2in{ewithpexp_desc=Pexp_apply(e1,les1@les2)}|_->appees2(* -------------------------------------------------------------------------- *)(* [sequence es] constructs a sequence of the expressions [es]. *)letsequence(es:expressions):expression=(* Using [fold_right1] instead of [List.fold_right] allows us to get
rid of a final [()] constant at the end of the sequence. Cosmetic. *)fold_right1(funeaccu->Exp.sequenceeaccu)es(unit())(* -------------------------------------------------------------------------- *)(* [vblet1 vb e] constructs a single [let] binding. *)letvblet1(vb:value_binding)(e:expression):expression=Exp.let_Nonrecursive[vb]e(* [let1 x e1 e2] constructs a single [let] binding. *)letlet1(x:variable)(e1:expression)(e2:expression):expression=vblet1(Vb.mk(pvarx)e1)e2(* [let1p x y e1 e2] constructs a single [let] binding of a pair. *)letlet1p(x,y:variable*variable)(e1:expression)(e2:expression):expression=vblet1(Vb.mk(ptuple[pvarx;pvary])e1)e2(* [vbletn vbs e] constructs a series of nested [let] bindings. *)letvbletn(vbs:value_bindinglist)(e:expression):expression=List.fold_rightvblet1vbse(* [letn xs es e] constructs a series of nested [let] bindings. *)letletn(xs:variables)(es:expressions)(e:expression)=List.fold_right2let1xsese(* [letnp xs ys es e] constructs a series of nested [let] bindings of pairs. *)letletnp(xs:variables)(ys:variables)(es:expressions)(e:expression)=List.fold_right2let1p(List.combinexsys)ese(* -------------------------------------------------------------------------- *)(* [access x label] constructs a record access expression [x.label]. *)letaccess(x:variable)(label:label):expression=Exp.field(evarx)(mknoloc(Lidentlabel))(* [accesses labels xs] constructs a matrix of record access expressions of
the form [x.label]. There is a row for every [label] and a column for every
[x]. *)letaccesses(xs:variables)(labels:labellist):expressionslist=List.map(funlabel->List.map(funx->accessxlabel)xs)labels(* -------------------------------------------------------------------------- *)(* [ptuple] is [Ast_convenience.ptuple], deprived of its optional arguments. *)letptuple(ps:patterns):pattern=ptupleps(* [ptuples] is [map ptuple]. *)letptuples(pss:patternslist):patterns=List.mapptuplepss(* -------------------------------------------------------------------------- *)(* The Boolean expressions [false] and [true]. *)letefalse:expression=Exp.construct(mknoloc(Lident"false"))Noneletetrue:expression=Exp.construct(mknoloc(Lident"true"))None(* -------------------------------------------------------------------------- *)(* [conjunction es] constructs a Boolean conjunction of the expressions [es]. *)letconjunction:expression=eident(pervasive"&&")letconjunctione1e2=appconjunction[e1;e2]letconjunction(es:expressions):expression=fold_right1conjunctionesetrue(* -------------------------------------------------------------------------- *)(* [eassertfalse] is the expression [assert false]. *)leteassertfalse:expression=Exp.assert_efalse(* -------------------------------------------------------------------------- *)(* [eforce e] is the expression [Lazy.force e]. *)leteforce:expression=eident(Longident.parse"Lazy.force")(* danger: the module name [Lazy] must not be shadowed. *)leteforce(e:expression):expression=appeforce[e](* -------------------------------------------------------------------------- *)(* [eqphy e1 e2] is the expression [e1 == e2]. *)leteqphy:expression=eident(pervasive"==")leteqphy(e1:expression)(e2:expression):expression=appeqphy[e1;e2](* [eqphys es1 es2] is the conjunction of the expressions [e1 == e2]. *)leteqphys(es1:expressions)(es2:expressions):expression=assert(List.lengthes1=List.lengthes2);conjunction(List.map2eqphyes1es2)(* -------------------------------------------------------------------------- *)(* [efail s] generates a call to [VisitorsRuntime.fail]. The parameter [s] is
a string, which could represent the place where a failure occurred, or the
reason why a failure occurred. As of now, it is unused. *)letefail:expression=eident(Ldot(Lident"VisitorsRuntime","fail"))(* danger: the module name [VisitorsRuntime] must not be shadowed. *)letefail(_:string):expression=appefail[unit()](* -------------------------------------------------------------------------- *)(* [include_ e] constructs an [include] declaration. *)letinclude_(e:module_expr):structure_item=Str.include_{pincl_mod=e;pincl_loc=Location.none;pincl_attributes=[];}(* -------------------------------------------------------------------------- *)(* [with_warnings w items] wraps the structure items [items] in such a way
that the warning directive [w] is applied to these items. Technically, this
is done by emitting [include struct [@@@ocaml.warning <w>] <items> end]. *)letwith_warnings(w:string)(items:structure_itemlist):structure_item=include_(Mod.structure(floating"ocaml.warning"[Str.eval(Exp.constant(const_stringw))]::items))(* -------------------------------------------------------------------------- *)(* [class1 concrete ancestors params name self fields] builds a class
declaration and packages it as a structure item. (This implies that it
cannot be recursive with other class declarations). *)letclass1(concrete:bool)(params:(core_type*variance)list)(name:classe)(self:pattern)(fields:class_fieldlist):structure_item=Str.class_[{pci_virt=ifconcretethenConcreteelseVirtual;pci_params=params;pci_name=mknolocname;pci_expr=Cl.structure(Cstr.mkselffields);pci_loc=!default_loc;pci_attributes=[];}](* -------------------------------------------------------------------------- *)(* [inherit_ c tys] builds an [inherit] clause, where the superclass is [c]
and its actual type parameters are [tys]. No [super] identifier is bound. *)letinherit_(c:Longident.t)(tys:core_types):class_field=Cf.inherit_Fresh(Cl.constr(mknolocc)tys)None(* -------------------------------------------------------------------------- *)(* An algebraic data type of the methods that we generate. These include
concrete methods (with code) and virtual methods (without code). They may
be public or private. The method type is optional. If omitted, then
it is inferred by OCaml. If present, it can be a polymorphic type. *)typemeth=Methofprivate_flag*methode*expressionoption*core_typeoptionletconcrete_methodpmeoty=Meth(p,m,Somee,oty)letvirtual_methodpmoty=Meth(p,m,None,oty)(* -------------------------------------------------------------------------- *)(* Converting a method description to OCaml abstract syntax. *)letoe2cfk(oe:expressionoption)(oty:core_typeoption):class_field_kind=matchoe,otywith|Somee,Some_->Cf.concreteFresh(Exp.polyeoty)|Somee,None->Cf.concreteFreshe|None,Somety->Cf.virtual_ty|None,None->Cf.virtual_ty_anyletmeth2cf(Meth(p,m,oe,oty)):class_field=Cf.method_(mknolocm)p(oe2cfkoeoty)(* -------------------------------------------------------------------------- *)(* [method_name] extracts a method name out of a method description. *)letmethod_name(Meth(_,m,_,_)):string=m(* -------------------------------------------------------------------------- *)(* [is_virtual] tests whether a method description represents a virtual
method. *)letis_virtual(Meth(_,_,oe,_)):bool=oe=None(* -------------------------------------------------------------------------- *)(* [send o m es] produces a call to the method [o#m] with arguments [es]. *)letsend(o:variable)(m:methode)(es:expressions):expression=app(exp_send(evaro)m)es(* -------------------------------------------------------------------------- *)(* An algebraic data type of the ``hoisted expressions'' that we generate. *)(* A ``hoisted expression'' is evaluated at most once after the object is
allocated. Its value is stored in an instance field. We allow such an
expression to reference [self], as long as it does not actually invoke any
methods. *)typehoisted=Hoistedofstring(* the name of the instance field *)*expression(* the hoisted expression *)(* -------------------------------------------------------------------------- *)(* Converting a hoisted field description to OCaml abstract syntax. *)(* We generate a mutable field declaration, followed with an initialization:
val mutable x = lazy (assert false)
initializer x <- lazy e
We must do this in two steps because the expression [e] might contain
references to [self], which are invalid in a field declaration, whereas
they are allowed in an initializer.
The potential danger in this idiom lies in forcing [x] before the
initializer has finished running, leading to an assertion failure.
This should not happen if [e] does not perform any method calls
or read any fields. *)lethoisted2cf(Hoisted(x,e)):class_fieldlist=[Cf.val_(mknolocx)(Mutable)(Cf.concreteFresh(Exp.lazy_eassertfalse));Cf.initializer_(Exp.setinstvar(mknolocx)(Exp.lazy_e))](* -------------------------------------------------------------------------- *)(* A facility for generating a class. *)moduleClassFieldStore(X:sigend):sig(* [generate meth] adds [meth] to the list of methods. *)valgenerate:meth->unit(* [hoist e] causes the expression [e] to be hoisted, that is, computed
once after the object is allocated. The result of evaluating [e] is
stored in a field. The call [hoist e] returns an expression which
reads this field. *)valhoist:expression->expression(* [dump concrete ancestors params self c] returns a class definition. *)valdump:bool->Longident.tlist->(core_type*variance)list->pattern->classe->structure_itemend=structletmeths:methlistref=ref[]letgeneratemeth=meths:=meth::!methsletdump():class_fieldlist=letmethods=List.rev!methsin(* Move all of the virtual methods up front. If two virtual methods have
the same name, keep only one of them. This is useful because we allow
a virtual method declaration to be generated several times. In fact,
OCaml supports this, but it looks tidier if we remove duplicates. *)letvirtual_methods,concrete_methods=List.partitionis_virtualmethodsinletcmpmeth1meth2=compare(method_namemeth1)(method_namemeth2)inletvirtual_methods=VisitorsList.weedcmpvirtual_methodsinletmethods=virtual_methods@concrete_methodsinList.mapmeth2cfmethodslethoisted:hoistedlistref=ref[]letfresh:unit->int=letc=ref0infun()->letx=!cinc:=x+1;xlethoist(e:expression):expression=letx=Printf.sprintf"h%d"(fresh())inhoisted:=Hoisted(x,e)::!hoisted;eforce(evarx)letdumpconcreteancestorsparamsselfc:structure_item=class1concreteparamscself((* [inherit] clauses. *)(* We ARBITRARILY assume that every ancestor class is parameterized
with ONE type parameter. *)List.map(func->inherit_c[ty_any])ancestors@(* Hoisted expressions. *)List.flatten(List.maphoisted2cf(List.rev!hoisted))@(* Methods. *)dump())end(* -------------------------------------------------------------------------- *)(* A facility for emitting preprocessor warnings. *)(* Warnings must be emitted under the form of [ppwarning] attributes, placed
in the generated code. This is not very convenient; we must store these
warnings, waiting for a convenient time to emit them. *)moduleWarningStore(X:sigend):sig(* [warning loc format ...] emits a warning. *)valwarning:loc->('a,unit,string,unit)format4->'a(* [warnings()] returns a list of all warnings emitted so far. *)valwarnings:unit->structureend=structletwarnings:attributelistref=ref[]letwarninglocmsg=warnings:=Ast_mapper.attribute_of_warninglocmsg::!warningsletwarninglocformat=Printf.ksprintf(warningloc)formatletwarnings()=letws=!warningsinwarnings:=[];List.map(funa->Str.attributea)(List.revws)end