Coccinelle release 1.0.0-rc14
[bpt/coccinelle.git] / parsing_cocci / ast_cocci.mli
index 16e0b1b..50304df 100644 (file)
@@ -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.
  *)
 
 
-(* 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.mli"
 (* --------------------------------------------------------------------- *)
 (* 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
 type 'a wrap =
@@ -46,6 +46,8 @@ type 'a wrap =
       bef_aft : dots_bef_aft;
       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 }
 
@@ -55,11 +57,14 @@ 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 *)
+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 (* ++ *)
@@ -86,13 +91,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 *)
@@ -102,7 +109,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 *)
@@ -111,6 +121,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
 
@@ -133,7 +145,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
 
@@ -148,6 +162,7 @@ and base_expression =
   | FunCall        of expression * string mcode (* ( *) *
                       expression dots * string mcode (* ) *)
   | Assignment     of expression * assignOp mcode * expression * bool
+  | Sequence       of expression * string mcode (* , *) * expression
   | CondExpr       of expression * string mcode (* ? *) * expression option *
                      string mcode (* : *) * expression
   | Postfix        of expression * fixOp mcode
@@ -170,17 +185,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 *
+  | 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 ...>)
@@ -194,16 +215,30 @@ 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
 
 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
 
@@ -222,7 +257,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
@@ -240,7 +277,9 @@ and base_typeC =
                    string mcode (* ) *)
   | 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 (* } *)
@@ -251,8 +290,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
 
@@ -272,11 +313,17 @@ 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 * string mcode (*;*)
   | DisjDecl   of declaration list
   | 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
@@ -288,8 +335,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 (*=*) *
@@ -297,6 +348,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
 
@@ -317,8 +369,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
 
@@ -360,7 +411,6 @@ and meta_collect = PER | ALL
 and meta_pos =
     MetaPos of meta_name mcode * meta_name list *
        meta_collect * keep_binding * inherited
-  | NoMetaPos
 
 (* --------------------------------------------------------------------- *)
 (* Function declaration *)
@@ -382,7 +432,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 *)
@@ -418,6 +468,7 @@ and base_rule_elem =
   | Ty            of fullType (* only at top level *)
   | 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 (*:*)
@@ -449,12 +500,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
@@ -502,7 +555,7 @@ and inc_elem =
   | IncDots
 
 and base_top_level =
-    DECL of statement
+    NONDECL of statement (* cannot match all of a top-level declaration *)
   | CODE of statement dots
   | FILEINFO of string mcode (* old file *) * string mcode (* new file *)
   | ERRORWORDS of expression list
@@ -516,9 +569,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
-  | 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
 
@@ -526,9 +582,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
-  | InitialScriptRule of string * string
-  | FinalScriptRule of string * 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 *)
@@ -537,7 +600,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
 
@@ -564,7 +627,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
@@ -611,10 +674,11 @@ val get_pos : 'a wrap -> meta_name mcode option
 val set_pos : 'a wrap -> meta_name mcode option -> 'a wrap
 val get_test_exp : 'a wrap -> bool
 val set_test_exp : expression -> expression
+val get_safe_decl : 'a wrap -> bool
 val get_isos : 'a wrap -> (string*anything) list
 val set_isos : 'a wrap -> (string*anything) list -> 'a wrap
-val get_pos_var : 'a mcode -> meta_pos
-val set_pos_var : meta_pos -> 'a mcode -> 'a mcode
+val get_pos_var : 'a mcode -> meta_pos list
+val set_pos_var : meta_pos list -> 'a mcode -> 'a mcode
 val drop_pos : 'a mcode -> 'a mcode
 
 val get_meta_name : metavar -> meta_name
@@ -634,6 +698,7 @@ val make_meta_decl :
       declaration
 
 val make_term : 'a -> 'a wrap
+val make_inherited_term : 'a -> meta_name list (* inherited vars *) -> 'a wrap
 val make_mcode : 'a -> 'a mcode
 
 val equal_pos : fixpos -> fixpos -> bool