Coccinelle release 1.0.0-rc14
[bpt/coccinelle.git] / parsing_cocci / ast_cocci.ml
index 1aa93a1..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
  *)
 
 
+# 0 "./ast_cocci.ml"
 (* --------------------------------------------------------------------- *)
 (* Modified code *)
 
-type added_string = Noindent of string | Indent of string
+type added_string = Noindent of string | Indent of string | Space of string
 
 type info = { line : int; column : int;
              strbef : (added_string * int (* line *) * int (* col *)) list;
@@ -57,12 +60,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 *)
     (* 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 *)
+    (* 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
@@ -71,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 (* ++ *)
@@ -104,6 +110,7 @@ and metavar =
   | 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*) * list_len (*len*)
@@ -119,6 +126,7 @@ and metavar =
   | 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 *)
@@ -151,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
@@ -168,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
@@ -190,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:
@@ -228,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 *)
@@ -241,7 +254,7 @@ and listlen =
   | 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
 
@@ -260,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
@@ -294,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
 
@@ -315,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
@@ -323,6 +343,8 @@ 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
@@ -334,6 +356,8 @@ 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 - *) *
@@ -408,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 *)
@@ -431,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 *)
@@ -492,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*)
@@ -501,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
@@ -559,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
@@ -685,7 +709,7 @@ 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
@@ -706,6 +730,7 @@ let get_meta_name = function
   | 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
@@ -717,6 +742,7 @@ let get_meta_name = function
   | 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
@@ -779,19 +805,33 @@ 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
-      (MetaRuleElem(((rule,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(((rule,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),[])
 
 (* --------------------------------------------------------------------- *)