X-Git-Url: https://git.hcoop.net/bpt/coccinelle.git/blobdiff_plain/113803cf8147c1b5332cc7d9ac43febcc197e4f0..785a3008ddade80f642257bb47d43158ac8b8311:/parsing_cocci/ast_cocci.mli diff --git a/parsing_cocci/ast_cocci.mli b/parsing_cocci/ast_cocci.mli index a207334..c086758 100644 --- a/parsing_cocci/ast_cocci.mli +++ b/parsing_cocci/ast_cocci.mli @@ -1,8 +1,11 @@ (* --------------------------------------------------------------------- *) (* Modified code *) +type added_string = Noindent of string | Indent of string + type info = { line : int; column : int; - strbef : string list; straft : string 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 type 'a wrap = @@ -10,7 +13,7 @@ type 'a wrap = node_line : line; free_vars : meta_name list; (*free vars*) minus_free_vars : meta_name list; (*minus free vars*) - fresh_vars : meta_name list; (*fresh vars*) + fresh_vars : (meta_name * seed) list; (*fresh vars*) inherited : meta_name list; (*inherited vars*) saved_witness : meta_name list; (*witness vars*) bef_aft : dots_bef_aft; @@ -20,18 +23,19 @@ type 'a wrap = iso_info : (string*anything) list } and 'a befaft = - BEFORE of 'a list list - | AFTER of 'a list list - | BEFOREAFTER of 'a list list * 'a list list + BEFORE of 'a list list * count + | AFTER of 'a list list * count + | BEFOREAFTER of 'a list list * 'a list list * count | NOTHING and 'a mcode = 'a * info * mcodekind * meta_pos (* pos variable *) (* pos is an offset indicating where in the C code the mcodekind has an effect *) and mcodekind = - MINUS of pos * anything list list + MINUS of pos * int list * int * anything list list | CONTEXT of pos * anything befaft - | PLUS + | PLUS of count + and count = ONE (* + *) | MANY (* ++ *) and fixpos = Real of int (* charpos *) | Virt of int * int (* charpos + offset *) and pos = NoPos | DontCarePos | FixPos of (fixpos * fixpos) @@ -46,8 +50,8 @@ and keep_binding = Type_cocci.keep_binding and multi = bool (*true if a nest is one or more, false if it is zero or more*) and end_info = - meta_name list (*free vars*) * meta_name list (*inherited vars*) * - meta_name list (*witness vars*) * mcodekind + meta_name list (*free vars*) * (meta_name * seed) list (*fresh*) * + meta_name list (*inherited vars*) * mcodekind (* --------------------------------------------------------------------- *) (* Metavariables *) @@ -56,12 +60,12 @@ and arity = UNIQUE | OPT | MULTI | NONE and metavar = MetaIdDecl of arity * meta_name (* name *) - | MetaFreshIdDecl of arity * meta_name (* name *) + | MetaFreshIdDecl of meta_name (* name *) * seed (* seed *) | MetaTypeDecl of arity * meta_name (* name *) | MetaInitDecl of arity * meta_name (* name *) | 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 *) @@ -71,7 +75,9 @@ 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 *) | MetaStmDecl of arity * meta_name (* name *) | MetaStmListDecl of arity * meta_name (* name *) | MetaFuncDecl of arity * meta_name (* name *) @@ -80,6 +86,11 @@ 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 + (* --------------------------------------------------------------------- *) (* --------------------------------------------------------------------- *) (* Dots *) @@ -95,11 +106,10 @@ and 'a dots = 'a base_dots wrap (* Identifier *) and base_ident = - Id of string mcode - - | MetaId of meta_name mcode * ident list * keep_binding * inherited - | MetaFunc of meta_name mcode * ident list * keep_binding * inherited - | MetaLocalFunc of meta_name mcode * ident list * keep_binding * inherited + Id of string mcode + | 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 | OptIdent of ident | UniqueIdent of ident @@ -137,17 +147,20 @@ and base_expression = | Paren of string mcode (* ( *) * expression * string mcode (* ) *) - | MetaErr of meta_name mcode * expression list * keep_binding * + | MetaErr of meta_name mcode * constraints * keep_binding * inherited - | MetaExpr of meta_name mcode * expression list * keep_binding * + | MetaExpr of meta_name mcode * constraints * keep_binding * Type_cocci.typeC list option * form * inherited - | MetaExprList of meta_name mcode * listlen option * + | MetaExprList of meta_name mcode * listlen * keep_binding * inherited (* only in arg lists *) | 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 ...>) @@ -159,11 +172,30 @@ and base_expression = | OptExp of expression | UniqueExp of expression +and constraints = + NoConstraint + | 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 * Str.regexp + | IdNotRegExp of string * Str.regexp + 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 assignOp = SimpleAssign | OpAssign of arithOp @@ -239,6 +271,7 @@ 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 | OptDecl of declaration | UniqueDecl of declaration @@ -251,7 +284,8 @@ and declaration = base_declaration wrap and base_initialiser = MetaInit of meta_name mcode * keep_binding * inherited | InitExpr of expression - | InitList of string mcode (*{*) * initialiser list * string mcode (*}*) * + | InitList 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 (*=*) * @@ -279,8 +313,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 @@ -398,7 +431,7 @@ and metaStmtInfo = and rule_elem = base_rule_elem wrap and base_statement = - Seq of rule_elem (* { *) * statement dots * + Seq of rule_elem (* { *) * statement dots * rule_elem (* } *) | IfThen of rule_elem (* header *) * statement * end_info | IfThenElse of rule_elem (* header *) * statement * @@ -408,14 +441,15 @@ and base_statement = | For of rule_elem (* header *) * statement * end_info | Iterator of rule_elem (* header *) * statement * end_info (*enditer*) | Switch of rule_elem (* header *) * rule_elem (* { *) * - case_line list * rule_elem (* } *) + 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 * statement dots * rule_elem (* } *) + statement dots * rule_elem (* } *) | Define of rule_elem (* header *) * statement dots | Dots of string mcode (* ... *) * (statement dots,statement) whencode list * @@ -478,7 +512,12 @@ and rulename = | GeneratedRulename of string option * dependency * string list * string list * exists * bool (* true if the whole thing is an expression *) - | ScriptRulename of string * dependency + | 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 @@ -486,7 +525,16 @@ and rule = CocciRule of string (* name *) * (dependency * string list (* dropped isos *) * exists) * top_level list * bool list (* true if generates an exp *) * ruletype - | ScriptRule of string * dependency * (string * meta_name) list * string + | ScriptRule of string (* name *) * + string * dependency * + (script_meta_name * meta_name * metavar) list * + meta_name list (*script vars*) * string + | InitialScriptRule of string (* name *) * + string * dependency * string + | FinalScriptRule of string (* name *) * + string * dependency * string + +and script_meta_name = string option (*string*) * string option (*ast*) and dependency = Dep of string (* rule applies for the current binding *) @@ -495,7 +543,7 @@ and dependency = | NeverDep of string (* rule never applies for any binding *) | AndDep of dependency * dependency | OrDep of dependency * dependency - | NoDep + | NoDep | FailDep and rule_with_metavars = metavar list * rule @@ -522,6 +570,7 @@ and anything = | CaseLineTag of case_line | ConstVolTag of const_vol | Token of string * info option + | Pragma of added_string list | Code of top_level | ExprDotsTag of expression dots | ParamDotsTag of parameterTypeDef dots @@ -534,7 +583,7 @@ and anything = (* --------------------------------------------------------------------- *) -and exists = Exists | Forall | ReverseForall | Undetermined +and exists = Exists | Forall | Undetermined (* --------------------------------------------------------------------- *) @@ -542,6 +591,8 @@ val mkToken : string -> anything val undots : 'a dots -> 'a list +val lub_count : count -> count -> count + (* --------------------------------------------------------------------- *) val rewrap : 'a wrap -> 'b -> 'b wrap @@ -551,12 +602,13 @@ val unwrap_mcode : 'a mcode -> 'a val get_mcodekind : 'a mcode -> mcodekind val get_line : 'a wrap -> line val get_mcode_line : 'a mcode -> line +val get_mcode_col : 'a mcode -> int val get_fvs : 'a wrap -> meta_name list val get_wcfvs : ('a wrap,'b wrap) whencode list -> meta_name list val set_fvs : meta_name list -> 'a wrap -> 'a wrap val get_mfvs : 'a wrap -> meta_name list val set_mfvs : meta_name list -> 'a wrap -> 'a wrap -val get_fresh : 'a wrap -> meta_name list +val get_fresh : 'a wrap -> (meta_name * seed) list val get_inherited : 'a wrap -> meta_name list val get_saved : 'a wrap -> meta_name list val get_dots_bef_aft : statement -> dots_bef_aft @@ -573,16 +625,18 @@ val drop_pos : 'a mcode -> 'a mcode val get_meta_name : metavar -> meta_name +val tag2c : anything -> string + val no_info : info val make_meta_rule_elem : string -> mcodekind -> - (meta_name list * meta_name list * meta_name list) -> + (meta_name list * (meta_name * seed) list * meta_name list) -> rule_elem val make_meta_decl : string -> mcodekind -> - (meta_name list * meta_name list * meta_name list) -> + (meta_name list * (meta_name * seed) list * meta_name list) -> declaration val make_term : 'a -> 'a wrap