Release coccinelle-0.2.4rc5
[bpt/coccinelle.git] / parsing_cocci / ast_cocci.ml
index 6f862b2..be1f50e 100644 (file)
@@ -1,4 +1,6 @@
 (*
+ * Copyright 2010, 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
-
 (* --------------------------------------------------------------------- *)
 (* Modified code *)
 
+type added_string = Noindent of string | Indent 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
@@ -64,7 +61,7 @@ and 'a mcode = 'a * info * mcodekind * meta_pos (* pos variable *)
     (* 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
+(* 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
@@ -106,7 +103,7 @@ and metavar =
   | 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 *)
@@ -116,7 +113,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 *)
@@ -125,6 +124,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
 
@@ -189,13 +190,16 @@ and base_expression =
                      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 *)
 
   | 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,15 +213,29 @@ 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 * Str.regexp
+  | IdNotRegExp     of string * Str.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  assignOp = SimpleAssign | OpAssign of arithOp
@@ -259,7 +277,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 (* } *)
@@ -298,6 +318,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
@@ -310,7 +331,9 @@ 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 (*}*) *
+  | 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 +341,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 +363,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
 
@@ -472,7 +495,8 @@ 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 (* { *) *
@@ -542,9 +566,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 +579,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 +625,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
@@ -673,6 +708,8 @@ 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
   | MetaStmDecl(ar,nm) -> nm
   | MetaStmListDecl(ar,nm) -> nm
   | MetaFuncDecl(ar,nm) -> nm
@@ -735,13 +772,15 @@ let make_term x =
     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,NoMetaPos),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,NoMetaPos),Type_cocci.Unitary,false))) with
     free_vars = fvs; fresh_vars = fresh; inherited = inh}
 
 let make_mcode x = (x,no_info,CONTEXT(NoPos,NOTHING),NoMetaPos)