123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408openPpxlibopenResultopenAsttypesopenParsetreeopenAst_helperopenPpx_derivingopenVisitorsPlugin(* This module offers helper functions for abstract syntax tree analysis. *)(* -------------------------------------------------------------------------- *)typetycon=stringtypetyvar=stringtypetyvars=tyvarlist(* -------------------------------------------------------------------------- *)(* Testing whether an identifier is valid. *)(* We use OCaml's lexer to analyze the string and check if it is a valid
identifier. This method is slightly unorthodox, as the lexer can have
undesired side effects, such as raising an [Error] exception or printing
warnings. We do our best to hide these effects. The strength of this
approach is to give us (at little cost) a correct criterion for deciding if
an identifier is valid. *)(* Note: [Location.formatter_for_warnings] appeared in OCaml 4.02.2. *)(* 2021/06/08 By default, [Parser] would be [Ppxlib.Parser], which exposes the
type [token] as an abstract type. Because we need the type [token] to be
concrete, we use [Ocaml_common.Parser] instead. [Ocaml_common] is part of
compiler-libs. *)typeclassification=|LIDENT|UIDENT|OTHERletclassify(s:string):classification=letlexbuf=Lexing.from_stringsinletbackup=!Ocaml_common.Location.formatter_for_warningsinletnull=Format.formatter_of_buffer(Buffer.create0)inOcaml_common.Location.formatter_for_warnings:=null;letresult=trylettoken1=Lexer.tokenlexbufinlettoken2=Lexer.tokenlexbufinletmoduleParser=Ocaml_common.Parserinmatchtoken1,token2with|Parser.LIDENT_,Parser.EOF->LIDENT|Parser.UIDENT_,Parser.EOF->UIDENT|_,_->OTHERwithLexer.Error_->OTHERinOcaml_common.Location.formatter_for_warnings:=backup;result(* -------------------------------------------------------------------------- *)(* Testing if a string is a valid [mod_longident], i.e., a possibly-qualified
module identifier. *)(* We might wish to use OCaml's parser for this purpose, but [mod_longident] is
not declared as a start symbol. Furthermore, that would be perhaps slightly
too lenient, e.g., allowing whitespace and comments inside. Our solution is
to split at the dots and check that every piece is a valid module name. *)(* We used to use [Longident.parse] to do the splitting, but this function has
been deprecated as of 4.11.0, and its suggested replacements do not go as
far back in time as we need. So, we use our own variant of this code. *)letrecparsesn=(* Parse the substring that extends from offset 0 to offset [n] excluded. *)tryleti=String.rindex_froms(n-1)'.'inletsegment=String.subs(i+1)(n-(i+1))inLdot(parsesi,segment)withNot_found->Lident(String.subs0n)letparses=parses(String.lengths)letis_valid_mod_longident(m:string):bool=String.lengthm>0&&letms=Longident.flatten_exn(parsem)inList.for_all(funm->classifym=UIDENT)ms(* -------------------------------------------------------------------------- *)(* Testing if a string is a valid [class_longident], i.e., a possibly-qualified
class identifier. *)letis_valid_class_longident(m:string):bool=String.lengthm>0&&matchparsemwith|Lidentc->classifyc=LIDENT|Ldot(m,c)->List.for_all(funm->classifym=UIDENT)(Longident.flatten_exnm)&&classifyc=LIDENT|Lapply_->assertfalse(* this cannot happen *)(* -------------------------------------------------------------------------- *)(* Testing if a string is a valid method name prefix. *)letis_valid_method_name_prefix(m:string):bool=String.lengthm>0&&classifym=LIDENT(* -------------------------------------------------------------------------- *)(* Testing for the presence of attributes. *)(* We use [ppx_deriving] to extract a specific attribute from an attribute
list. By convention, an attribute named [foo] can also be referred to as
[visitors.foo] or as [deriving.visitors.foo]. *)(* [select foo attrs] extracts the attribute named [foo] from the attribute
list [attrs]. *)letselect(foo:string)(attrs:attributes):attributeoption=attr~deriver:pluginfooattrs(* [present foo attrs] tests whether an attribute named [foo] is present
(with no argument) in the list [attrs]. *)letpresent(foo:string)(attrs:attributes):bool=Arg.get_flag~deriver:plugin(selectfooattrs)(* [opacity attrs] tests for the presence of an [@opaque] attribute. *)typeopacity=|Opaque|NonOpaqueletopacity(attrs:attributes):opacity=ifpresent"opaque"attrsthenOpaqueelseNonOpaque(* [name attrs] tests for the presence of a [@name] attribute, carrying a
payload of type [string]. We check that the payload is a valid (lowercase
or uppercase) identifier, because we intend to use it as the basis of a
method name. *)letidentifier:stringArg.conv=fune->matchArg.stringewith|Errormsg->Errormsg|Oks->matchclassifyswith|LIDENT|UIDENT->Oks|OTHER->Error"identifier"letname(attrs:attributes):stringoption=Arg.get_attr~deriver:pluginidentifier(select"name"attrs)(* [build attrs] tests for the presence of a [@build] attribute,
carrying a payload that is an arbitrary OCaml expression. *)letbuild(attrs:attributes):expressionoption=Arg.get_attr~deriver:pluginArg.expr(select"build"attrs)(* [maybe ox y] returns [x] if present, otherwise [y]. *)letmaybe(ox:'aoption)(y:'a):'a=matchoxwithSomex->x|None->y(* -------------------------------------------------------------------------- *)(* When parsing a record declaration, the OCaml parser attaches attributes
with field labels, whereas the user might naturally expect them to be
attached with the type. We rectify this situation by copying all attributes
from the label to the type. This might seem dangerous, but we use it only
to test for the presence of an [@opaque] attribute. *)letpaste(ty:core_type)(attrs:attributes):core_type={tywithptyp_attributes=attrs@ty.ptyp_attributes}letfix(ld:label_declaration):label_declaration={ldwithpld_type=pasteld.pld_typeld.pld_attributes}letfix=List.mapfix(* -------------------------------------------------------------------------- *)(* [type_param_to_tyvar] expects a type parameter as found in the field
[ptype_params] of a type definition, and returns the underlying type
variable. *)lettype_param_to_tyvar((ty,_):core_type*(variance*injectivity)):tyvar=matchty.ptyp_descwith|Ptyp_vartv->tv|Ptyp_any->(* This error occurs if a formal type parameter is a wildcard [_].
We could support this form, but it makes life slightly simpler
to disallow it. It is usually used only in GADTs anyway. *)raise_errorf~loc:ty.ptyp_loc"%s: every formal type parameter should be named."plugin|_->assertfalselettype_params_to_tyvars=List.maptype_param_to_tyvar(* [decl_params decl] returns the type parameters of the declaration [decl]. *)letdecl_params(decl:type_declaration):tyvars=type_params_to_tyvarsdecl.ptype_params(* [is_local decls tycon] tests whether the type constructor [tycon] is
declared by the type declarations [decls]. If so, it returns the
corresponding declaration. *)letrecis_local(decls:type_declarationlist)(tycon:tycon):type_declarationoption=matchdeclswith|[]->None|decl::decls->ifdecl.ptype_name.txt=tyconthenSomedeclelseis_localdeclstyconletis_local(decls:type_declarationlist)(tycon:Longident.t):type_declarationoption=matchtyconwith|Lidenttycon->is_localdeclstycon|Ldot_|Lapply_->None(* -------------------------------------------------------------------------- *)(* [occurs_type alpha ty] tests whether the type variable [alpha] occurs in
the type [ty]. This function goes down into all OCaml types, even those
that are not supported by [visitors]. *)exceptionOccursoflocletrecoccurs_type(alpha:tyvar)(ty:core_type):unit=matchty.ptyp_descwith|Ptyp_any->()|Ptyp_varbeta->ifalpha=betathenraise(Occursty.ptyp_loc)|Ptyp_alias(ty,_)->(* This is not a binder; just go down into it. *)occurs_typealphaty|Ptyp_arrow(_,ty1,ty2)->occurs_typesalpha[ty1;ty2]|Ptyp_tupletys|Ptyp_constr(_,tys)|Ptyp_class(_,tys)->occurs_typesalphatys|Ptyp_object(fields,_)->fields|>List.mapVisitorsCompatibility.object_field_to_core_type|>occurs_typesalpha|Ptyp_variant(fields,_,_)->List.iter(occurs_row_fieldalpha)fields|Ptyp_poly(qs,ty)->letqs:stringlist=VisitorsCompatibility.quantifiersqsin(* The type variables in [qs] are bound. *)ifnot(occurs_quantifiersalphaqs)thenoccurs_typealphaty|Ptyp_package(_,ltys)->List.iter(fun(_,ty)->occurs_typealphaty)ltys|Ptyp_extension(_,payload)->occurs_payloadalphapayloadandoccurs_typesalphatys=List.iter(occurs_typealpha)tysandoccurs_row_fieldalphafield=field|>VisitorsCompatibility.row_field_to_core_types|>occurs_typesalphaandoccurs_quantifiersalpha(qs:stringlist)=List.memalphaqsandoccurs_payloadalpha=function|PTypty->occurs_typealphaty(* | PStr _ | PPat _ *)(* | PSig _ (* >= 4.03 *) *)|_->(* We assume that these cases won't arise or won't have any free type
variables in them. *)()(* -------------------------------------------------------------------------- *)(* An error message about an unsupported type. *)letunsupportedty=letloc=ty.ptyp_locinraise_errorf~loc"%s: cannot deal with the type %s.\n\
Consider annotating it with [@opaque]."plugin(string_of_core_typety)(* -------------------------------------------------------------------------- *)(* [at_opaque f ty] applies the function [f] to every [@opaque] component of
the type [ty]. *)letrecat_opaque(f:core_type->unit)(ty:core_type):unit=matchopacityty.ptyp_attributes,ty.ptyp_descwith|NonOpaque,Ptyp_any|NonOpaque,Ptyp_var_->()|NonOpaque,Ptyp_tupletys|NonOpaque,Ptyp_constr(_,tys)->List.iter(at_opaquef)tys|Opaque,_->fty|NonOpaque,Ptyp_arrow_|NonOpaque,Ptyp_object_|NonOpaque,Ptyp_class_|NonOpaque,Ptyp_alias_|NonOpaque,Ptyp_variant_|NonOpaque,Ptyp_poly_|NonOpaque,Ptyp_package_|NonOpaque,Ptyp_extension_->unsupportedty(* -------------------------------------------------------------------------- *)(* [check_poly_under_opaque alphas tys] checks that none of the type variables
[alphas] appears under [@opaque] in the types [tys]. *)letcheck_poly_under_opaquealphastys=List.iter(funalpha->List.iter(funty->at_opaque(funty->tryoccurs_typealphatywithOccursloc->raise_errorf~loc"%s: a [polymorphic] type variable must not appear under @opaque."plugin)ty)tys)alphas(* -------------------------------------------------------------------------- *)(* [subst_type sigma ty] applies [sigma], a substitution of types for type
variables, to the type [ty].
[rename_type rho ty] applies [rho], a renaming of type variables, to the
type [ty]. *)(* We do not go down into [@opaque] types. We replace every opaque type with a
wildcard [_]. Because we have checked that [poly] variables do not appear
under [@opaque], this is good enough: there is never a need for an
explicitly named/quantified type variable to describe an opaque
component. *)typesubstitution=tyvar->core_typetyperenaming=tyvar->tyvarletrecsubst_type(sigma:substitution)(ty:core_type):core_type=matchopacityty.ptyp_attributes,ty.ptyp_descwith|NonOpaque,Ptyp_any->ty|NonOpaque,Ptyp_varalpha->sigmaalpha|NonOpaque,Ptyp_tupletys->{tywithptyp_desc=Ptyp_tuple(subst_typessigmatys)}|NonOpaque,Ptyp_constr(tycon,tys)->{tywithptyp_desc=Ptyp_constr(tycon,subst_typessigmatys)}|Opaque,_->Typ.any()|NonOpaque,Ptyp_arrow_|NonOpaque,Ptyp_object_|NonOpaque,Ptyp_class_|NonOpaque,Ptyp_alias_|NonOpaque,Ptyp_variant_|NonOpaque,Ptyp_poly_|NonOpaque,Ptyp_package_|NonOpaque,Ptyp_extension_->unsupportedtyandsubst_typessigmatys=List.map(subst_typesigma)tysletrename_type(rho:renaming)(ty:core_type):core_type=subst_type(funalpha->Typ.var(rhoalpha))ty