X-Git-Url: https://git.hcoop.net/bpt/coccinelle.git/blobdiff_plain/9f8e26f459677a621822918b7539ae94214621ac..7f339edd551eefcd6c99f379ce91c27df997cfe3:/parsing_cocci/ast_cocci.ml diff --git a/parsing_cocci/ast_cocci.ml b/parsing_cocci/ast_cocci.ml index 6f862b2..cdc165b 100644 --- a/parsing_cocci/ast_cocci.ml +++ b/parsing_cocci/ast_cocci.ml @@ -1,4 +1,8 @@ (* + * Copyright 2012, INRIA + * Julia Lawall, Gilles Muller + * Copyright 2010-2011, INRIA, University of Copenhagen + * Julia Lawall, Rene Rydhof Hansen, Gilles Muller, Nicolas Palix * Copyright 2005-2009, Ecole des Mines de Nantes, University of Copenhagen * Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller, Nicolas Palix * This file is part of Coccinelle. @@ -20,19 +24,15 @@ *) -(* Constraints on Meta-* Identifiers, Functions *) -type idconstraint = - IdNoConstraint - | IdNegIdSet of string list - | IdRegExp of string * Str.regexp - | IdNotRegExp of string * Str.regexp - +# 0 "./ast_cocci.ml" (* --------------------------------------------------------------------- *) (* Modified code *) +type added_string = Noindent of string | Indent of string | Space of string + type info = { line : int; column : int; - strbef : (string * int (* line *) * int (* col *)) list; - straft : (string * int (* line *) * int (* col *)) list } + strbef : (added_string * int (* line *) * int (* col *)) list; + straft : (added_string * int (* line *) * int (* col *)) list } type line = int type meta_name = string * string (* need to be careful about rewrapping, to avoid duplicating pos info @@ -49,6 +49,8 @@ type 'a wrap = (* the following is for or expressions *) pos_info : meta_name mcode option; (* pos info, try not to duplicate *) true_if_test_exp : bool;(* true if "test_exp from iso", only for exprs *) + (* the following is only for declarations *) + safe_for_multi_decls : bool; (* isos relevant to the term; ultimately only used for rule_elems *) iso_info : (string*anything) list } @@ -58,13 +60,15 @@ and 'a befaft = | BEFOREAFTER of 'a list list * 'a list list * count | NOTHING -and 'a mcode = 'a * info * mcodekind * meta_pos (* pos variable *) +and 'a replacement = REPLACEMENT of 'a list list * count | NOREPLACEMENT + +and 'a mcode = 'a * info * mcodekind * meta_pos list (* pos variables *) (* pos is an offset indicating where in the C code the mcodekind has an effect *) (* int list is the match instances, which are only meaningful in annotated C code *) - (* int is the adjacency index, which is incremented on context dots *) -(* iteration is only allowed on contect code, the intuition vaguely being + (* adjacency is the adjacency index, which is incremented on context dots *) +(* iteration is only allowed on context code, the intuition vaguely being that there is no way to replace something more than once. Actually, allowing iterated additions on minus code would cause problems with some heuristics for adding braces, because one couldn't identify simple @@ -72,8 +76,9 @@ replacements with certainty. Anyway, iteration doesn't seem to be needed on - code for the moment. Although it may be confusing that there can be iterated addition of code before context code where the context code is immediately followed by removed code. *) +and adjacency = ALLMINUS | ADJ of int and mcodekind = - MINUS of pos * int list * int * anything list list + MINUS of pos * int list * adjacency * anything replacement | CONTEXT of pos * anything befaft | PLUS of count and count = ONE (* + *) | MANY (* ++ *) @@ -100,13 +105,15 @@ and end_info = and arity = UNIQUE | OPT | MULTI | NONE and metavar = - MetaIdDecl of arity * meta_name (* name *) + MetaMetaDecl of arity * meta_name (* name *) + | MetaIdDecl of arity * meta_name (* name *) | MetaFreshIdDecl of meta_name (* name *) * seed (* seed *) | MetaTypeDecl of arity * meta_name (* name *) | MetaInitDecl of arity * meta_name (* name *) + | MetaInitListDecl of arity * meta_name (* name *) * list_len (*len*) | MetaListlenDecl of meta_name (* name *) | MetaParamDecl of arity * meta_name (* name *) - | MetaParamListDecl of arity * meta_name (*name*) * meta_name option (*len*) + | MetaParamListDecl of arity * meta_name (*name*) * list_len (*len*) | MetaConstDecl of arity * meta_name (* name *) * Type_cocci.typeC list option | MetaErrDecl of arity * meta_name (* name *) @@ -116,7 +123,10 @@ and metavar = arity * meta_name (* name *) * Type_cocci.typeC list option | MetaLocalIdExpDecl of arity * meta_name (* name *) * Type_cocci.typeC list option - | MetaExpListDecl of arity * meta_name (*name*) * meta_name option (*len*) + | MetaExpListDecl of arity * meta_name (*name*) * list_len (*len*) + | MetaDeclDecl of arity * meta_name (* name *) + | MetaFieldDecl of arity * meta_name (* name *) + | MetaFieldListDecl of arity * meta_name (* name *) * list_len (*len*) | MetaStmDecl of arity * meta_name (* name *) | MetaStmListDecl of arity * meta_name (* name *) | MetaFuncDecl of arity * meta_name (* name *) @@ -125,6 +135,8 @@ and metavar = | MetaDeclarerDecl of arity * meta_name (* name *) | MetaIteratorDecl of arity * meta_name (* name *) +and list_len = AnyLen | MetaLen of meta_name | CstLen of int + and seed = NoVal | StringSeed of string | ListSeed of seed_elem list and seed_elem = SeedString of string | SeedId of meta_name @@ -147,7 +159,9 @@ and base_ident = | MetaId of meta_name mcode * idconstraint * keep_binding * inherited | MetaFunc of meta_name mcode * idconstraint * keep_binding * inherited | MetaLocalFunc of meta_name mcode * idconstraint * keep_binding * inherited + | AsIdent of ident * ident (* as ident, always metavar *) + | DisjId of ident list | OptIdent of ident | UniqueIdent of ident @@ -163,6 +177,7 @@ and base_expression = expression dots * string mcode (* ) *) | Assignment of expression * assignOp mcode * expression * bool (* true if it can match an initialization *) + | Sequence of expression * string mcode (* , *) * expression | CondExpr of expression * string mcode (* ? *) * expression option * string mcode (* : *) * expression | Postfix of expression * fixOp mcode @@ -185,17 +200,23 @@ and base_expression = | Paren of string mcode (* ( *) * expression * string mcode (* ) *) + | Constructor of string mcode (* ( *) * fullType * string mcode (* ) *) * + initialiser | MetaErr of meta_name mcode * constraints * keep_binding * inherited | MetaExpr of meta_name mcode * constraints * keep_binding * Type_cocci.typeC list option * form * inherited - | MetaExprList of meta_name mcode * listlen option * keep_binding * + | MetaExprList of meta_name mcode * listlen * keep_binding * inherited (* only in arg lists *) + | AsExpr of expression * expression (* as expr, always metavar *) | EComma of string mcode (* only in arg lists *) | DisjExpr of expression list - | NestExpr of expression dots * expression option * multi + | NestExpr of string mcode (* <.../<+... *) * + expression dots * + string mcode (* ...>/...+> *) * + expression option * multi (* can appear in arg lists, and also inside Nest, as in: if(< ... X ... Y ...>) @@ -209,17 +230,31 @@ and base_expression = and constraints = NoConstraint - | NotIdCstrt of idconstraint + | NotIdCstrt of reconstraint | NotExpCstrt of expression list + | SubExpCstrt of meta_name list + +(* Constraints on Meta-* Identifiers, Functions *) +and idconstraint = + IdNoConstraint + | IdNegIdSet of string list * meta_name list + | IdRegExpConstraint of reconstraint + +and reconstraint = + | IdRegExp of string * Regexp.regexp + | IdNotRegExp of string * Regexp.regexp (* ANY = int E; ID = idexpression int X; CONST = constant int X; *) and form = ANY | ID | LocalID | CONST (* form for MetaExp *) and expression = base_expression wrap -and listlen = meta_name mcode * keep_binding * inherited +and listlen = + MetaListLen of meta_name mcode * keep_binding * inherited + | CstListLen of int + | AnyListLen -and unaryOp = GetRef | DeRef | UnPlus | UnMinus | Tilde | Not +and unaryOp = GetRef | GetRefLabel | DeRef | UnPlus | UnMinus | Tilde | Not and assignOp = SimpleAssign | OpAssign of arithOp and fixOp = Dec | Inc @@ -238,7 +273,9 @@ and constant = (* Types *) and base_fullType = - Type of const_vol mcode option * typeC + Type of bool (* true if all minus *) * + const_vol mcode option * typeC + | AsType of fullType * fullType (* as type, always metavar *) | DisjType of fullType list (* only after iso *) | OptType of fullType | UniqueType of fullType @@ -259,7 +296,9 @@ and base_typeC = | Array of fullType * string mcode (* [ *) * expression option * string mcode (* ] *) - | EnumName of string mcode (*enum*) * ident (* name *) + | EnumName of string mcode (*enum*) * ident option (* name *) + | EnumDef of fullType (* either EnumName or metavar *) * + string mcode (* { *) * expression dots * string mcode (* } *) | StructUnionName of structUnion mcode * ident option (* name *) | StructUnionDef of fullType (* either StructUnionName or metavar *) * string mcode (* { *) * declaration dots * string mcode (* } *) @@ -270,8 +309,10 @@ and base_typeC = and fullType = base_fullType wrap and typeC = base_typeC wrap -and baseType = VoidType | CharType | ShortType | IntType | DoubleType - | FloatType | LongType | LongLongType +and baseType = VoidType | CharType | ShortType | ShortIntType | IntType +| DoubleType | LongDoubleType | FloatType +| LongType | LongIntType | LongLongType | LongLongIntType +| SizeType | SSizeType | PtrDiffType and structUnion = Struct | Union @@ -291,6 +332,9 @@ and base_declaration = | TyDecl of fullType * string mcode (* ; *) | MacroDecl of ident (* name *) * string mcode (* ( *) * expression dots * string mcode (* ) *) * string mcode (* ; *) + | MacroDeclInit of ident (* name *) * string mcode (* ( *) * + expression dots * string mcode (* ) *) * string mcode (*=*) * + initialiser * string mcode (* ; *) | Typedef of string mcode (*typedef*) * fullType * typeC (* either TypeName or metavar *) * string mcode (*;*) | DisjDecl of declaration list @@ -298,6 +342,9 @@ and base_declaration = | Ddots of string mcode (* ... *) * declaration option (* whencode *) | MetaDecl of meta_name mcode * keep_binding * inherited + | MetaField of meta_name mcode * keep_binding * inherited + | MetaFieldList of meta_name mcode * listlen * keep_binding * inherited + | AsDecl of declaration * declaration | OptDecl of declaration | UniqueDecl of declaration @@ -309,8 +356,12 @@ and declaration = base_declaration wrap and base_initialiser = MetaInit of meta_name mcode * keep_binding * inherited + | MetaInitList of meta_name mcode * listlen * keep_binding * inherited + | AsInit of initialiser * initialiser (* as init, always metavar *) | InitExpr of expression - | InitList of string mcode (*{*) * initialiser list * string mcode (*}*) * + | ArInitList of string mcode (*{*) * initialiser dots * string mcode (*}*) + | StrInitList of bool (* true if all are - *) * + string mcode (*{*) * initialiser list * string mcode (*}*) * initialiser list (* whencode: elements that shouldn't appear in init *) | InitGccExt of designator list (* name *) * string mcode (*=*) * @@ -318,6 +369,7 @@ and base_initialiser = | InitGccName of ident (* name *) * string mcode (*:*) * initialiser | IComma of string mcode (* , *) + | Idots of string mcode (* ... *) * initialiser option (* whencode *) | OptIni of initialiser | UniqueIni of initialiser @@ -339,8 +391,7 @@ and base_parameterTypeDef = | Param of fullType * ident option | MetaParam of meta_name mcode * keep_binding * inherited - | MetaParamList of meta_name mcode * listlen option * keep_binding * - inherited + | MetaParamList of meta_name mcode * listlen * keep_binding * inherited | PComma of string mcode @@ -381,8 +432,7 @@ and meta_collect = PER | ALL and meta_pos = MetaPos of meta_name mcode * meta_name list * - meta_collect * keep_binding * inherited - | NoMetaPos + meta_collect * keep_binding * inherited (* --------------------------------------------------------------------- *) (* Function declaration *) @@ -404,7 +454,7 @@ and base_rule_elem = | SeqStart of string mcode (* { *) | SeqEnd of string mcode (* } *) - | ExprStatement of expression * string mcode (*;*) + | ExprStatement of expression option * string mcode (*;*) | IfHeader of string mcode (* if *) * string mcode (* ( *) * expression * string mcode (* ) *) | Else of string mcode (* else *) @@ -441,6 +491,7 @@ and base_rule_elem = | Ty of fullType (* only at SP top level, matches a subterm *) | TopInit of initialiser (* only at top level *) | Include of string mcode (*#include*) * inc_file mcode (*file *) + | Undef of string mcode (* #define *) * ident (* name *) | DefineHeader of string mcode (* #define *) * ident (* name *) * define_parameters (*params*) | Case of string mcode (* case *) * expression * string mcode (*:*) @@ -464,7 +515,7 @@ and base_statement = | IfThen of rule_elem (* header *) * statement * end_info (* endif *) | IfThenElse of rule_elem (* header *) * statement * rule_elem (* else *) * statement * end_info (* endif *) - | While of rule_elem (* header *) * statement * end_info (*endwhile*) + | While of rule_elem (* header *) * statement * end_info(*endwhile*) | Do of rule_elem (* do *) * statement * rule_elem (* tail *) | For of rule_elem (* header *) * statement * end_info (*endfor*) | Iterator of rule_elem (* header *) * statement * end_info (*enditer*) @@ -472,12 +523,14 @@ and base_statement = statement (*decl*) dots * case_line list * rule_elem(*}*) | Atomic of rule_elem | Disj of statement dots list - | Nest of statement dots * + | Nest of string mcode (* <.../<+... *) * statement dots * + string mcode (* ...>/...+> *) * (statement dots,statement) whencode list * multi * dots_whencode list * dots_whencode list | FunDecl of rule_elem (* header *) * rule_elem (* { *) * statement dots * rule_elem (* } *) | Define of rule_elem (* header *) * statement dots + | AsStmt of statement * statement (* as statement, always metavar *) | Dots of string mcode (* ... *) * (statement dots,statement) whencode list * dots_whencode list * dots_whencode list @@ -530,7 +583,7 @@ and inc_elem = | IncDots and base_top_level = - DECL of statement + NONDECL of statement | CODE of statement dots | FILEINFO of string mcode (* old file *) * string mcode (* new file *) | ERRORWORDS of expression list @@ -542,9 +595,12 @@ and rulename = string list * string list * exists * bool | GeneratedRulename of string option * dependency * string list * string list * exists * bool - | ScriptRulename of string * dependency - | InitialScriptRulename of string - | FinalScriptRulename of string + | ScriptRulename of string option (* name *) * string (* language *) * + dependency + | InitialScriptRulename of string option (* name *) * string (* language *) * + dependency + | FinalScriptRulename of string option (* name *) * string (* language *) * + dependency and ruletype = Normal | Generated @@ -552,9 +608,17 @@ and rule = CocciRule of string (* name *) * (dependency * string list (* dropped isos *) * exists) * top_level list * bool list * ruletype - | ScriptRule of string * dependency * (string * meta_name) list * string - | InitialScriptRule of string (*language*) * string (*code*) - | FinalScriptRule of string (*language*) * string (*code*) + | ScriptRule of string (* name *) * + (* metaname for python (untyped), metavar for ocaml (typed) *) + string * dependency * + (script_meta_name * meta_name * metavar) list (*inherited vars*) * + meta_name list (*script vars*) * string + | InitialScriptRule of string (* name *) * + string (*language*) * dependency * string (*code*) + | FinalScriptRule of string (* name *) * + string (*language*) * dependency * string (*code*) + +and script_meta_name = string option (*string*) * string option (*ast*) and dependency = Dep of string (* rule applies for the current binding *) @@ -590,7 +654,7 @@ and anything = | CaseLineTag of case_line | ConstVolTag of const_vol | Token of string * info option - | Pragma of string list + | Pragma of added_string list | Code of top_level | ExprDotsTag of expression dots | ParamDotsTag of parameterTypeDef dots @@ -638,13 +702,14 @@ let get_dots_bef_aft x = x.bef_aft let set_dots_bef_aft d x = {x with bef_aft = d} let get_pos x = x.pos_info let set_pos x pos = {x with pos_info = pos} -let get_test_exp x = x.true_if_test_exp -let set_test_exp x = {x with true_if_test_exp = true} +let get_test_exp x = x.true_if_test_exp +let set_test_exp x = {x with true_if_test_exp = true} +let get_safe_decl x = x.safe_for_multi_decls let get_isos x = x.iso_info let set_isos x isos = {x with iso_info = isos} let get_pos_var (_,_,_,p) = p let set_pos_var vr (a,b,c,_) = (a,b,c,vr) -let drop_pos (a,b,c,_) = (a,b,c,NoMetaPos) +let drop_pos (a,b,c,_) = (a,b,c,[]) let get_wcfvs (whencode : ('a wrap, 'b wrap) whencode list) = Common.union_all @@ -660,10 +725,12 @@ let get_wcfvs (whencode : ('a wrap, 'b wrap) whencode list) = (* --------------------------------------------------------------------- *) let get_meta_name = function - MetaIdDecl(ar,nm) -> nm + MetaMetaDecl(ar,nm) -> nm + | MetaIdDecl(ar,nm) -> nm | MetaFreshIdDecl(nm,seed) -> nm | MetaTypeDecl(ar,nm) -> nm | MetaInitDecl(ar,nm) -> nm + | MetaInitListDecl(ar,nm,nm1) -> nm | MetaListlenDecl(nm) -> nm | MetaParamDecl(ar,nm) -> nm | MetaParamListDecl(ar,nm,nm1) -> nm @@ -673,6 +740,9 @@ let get_meta_name = function | MetaIdExpDecl(ar,nm,ty) -> nm | MetaLocalIdExpDecl(ar,nm,ty) -> nm | MetaExpListDecl(ar,nm,nm1) -> nm + | MetaDeclDecl(ar,nm) -> nm + | MetaFieldDecl(ar,nm) -> nm + | MetaFieldListDecl(ar,nm,nm1) -> nm | MetaStmDecl(ar,nm) -> nm | MetaStmListDecl(ar,nm) -> nm | MetaFuncDecl(ar,nm) -> nm @@ -732,19 +802,36 @@ let make_term x = bef_aft = NoDots; pos_info = None; true_if_test_exp = false; + safe_for_multi_decls = false; + iso_info = [] } + +let make_inherited_term x inherited = + {node = x; + node_line = 0; + free_vars = []; + minus_free_vars = []; + fresh_vars = []; + inherited = inherited; + saved_witness = []; + bef_aft = NoDots; + pos_info = None; + true_if_test_exp = false; + safe_for_multi_decls = false; iso_info = [] } let make_meta_rule_elem s d (fvs,fresh,inh) = + let rule = "" in {(make_term - (MetaRuleElem((("",s),no_info,d,NoMetaPos),Type_cocci.Unitary,false))) + (MetaRuleElem(((rule,s),no_info,d,[]),Type_cocci.Unitary,false))) with free_vars = fvs; fresh_vars = fresh; inherited = inh} let make_meta_decl s d (fvs,fresh,inh) = + let rule = "" in {(make_term - (MetaDecl((("",s),no_info,d,NoMetaPos),Type_cocci.Unitary,false))) with + (MetaDecl(((rule,s),no_info,d,[]),Type_cocci.Unitary,false))) with free_vars = fvs; fresh_vars = fresh; inherited = inh} -let make_mcode x = (x,no_info,CONTEXT(NoPos,NOTHING),NoMetaPos) +let make_mcode x = (x,no_info,CONTEXT(NoPos,NOTHING),[]) (* --------------------------------------------------------------------- *)