Coccinelle release 1.0.0-rc14
[bpt/coccinelle.git] / parsing_cocci / ast_cocci.ml
index c95eab5..cdc165b 100644 (file)
@@ -1,5 +1,7 @@
 (*
- * Copyright 2010, INRIA, University of Copenhagen
+ * 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
@@ -22,6 +24,7 @@
  *)
 
 
+# 0 "./ast_cocci.ml"
 (* --------------------------------------------------------------------- *)
 (* Modified code *)
 
@@ -156,6 +159,7 @@ 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
@@ -173,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
@@ -195,19 +200,22 @@ 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 * 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 string mcode (* <.../<+... *) *
                      expression dots *
-                     string mcode (* ...>/...+> *) * 
+                     string mcode (* ...>/...+> *) *
                       expression option * multi
 
   (* can appear in arg lists, and also inside Nest, as in:
@@ -233,8 +241,8 @@ and idconstraint =
   | IdRegExpConstraint of reconstraint
 
 and reconstraint =
-  | IdRegExp        of string * Str.regexp
-  | IdNotRegExp     of string * Str.regexp
+  | 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 *)
@@ -265,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
@@ -299,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 | SizeType | SSizeType | PtrDiffType
+and baseType = VoidType | CharType | ShortType | ShortIntType | IntType
+| DoubleType | LongDoubleType | FloatType
+| LongType | LongIntType | LongLongType | LongLongIntType
+| SizeType | SSizeType | PtrDiffType
 
 and structUnion = Struct | Union
 
@@ -320,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
@@ -329,6 +344,7 @@ and base_declaration =
   | 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
@@ -341,6 +357,7 @@ 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
   | ArInitList of string mcode (*{*) * initialiser dots * string mcode (*}*)
   | StrInitList of bool (* true if all are - *) *
@@ -498,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*)
@@ -507,12 +524,13 @@ and base_statement =
   | Atomic        of rule_elem
   | Disj          of statement dots list
   | Nest          of string mcode (* <.../<+... *) * statement dots *
-                    string mcode (* ...>/...+> *) * 
+                    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
@@ -565,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
@@ -787,6 +805,20 @@ let make_term x =
     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