X-Git-Url: http://git.hcoop.net/bpt/coccinelle.git/blobdiff_plain/34e491640531bd81a0e2238fd599e1aafe53613e..aba5c4579802a0df4fc1e60559a8ff389cc0cc42:/parsing_cocci/ast0_cocci.ml diff --git a/parsing_cocci/ast0_cocci.ml b/parsing_cocci/ast0_cocci.ml index 5175cf7..fbdd107 100644 --- a/parsing_cocci/ast0_cocci.ml +++ b/parsing_cocci/ast0_cocci.ml @@ -1,23 +1,25 @@ (* -* Copyright 2005-2008, Ecole des Mines de Nantes, University of Copenhagen -* Yoann Padioleau, Julia Lawall, Rene Rydhof Hansen, Henrik Stuart, Gilles Muller -* This file is part of Coccinelle. -* -* Coccinelle is free software: you can redistribute it and/or modify -* it under the terms of the GNU General Public License as published by -* the Free Software Foundation, according to version 2 of the License. -* -* Coccinelle is distributed in the hope that it will be useful, -* but WITHOUT ANY WARRANTY; without even the implied warranty of -* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -* GNU General Public License for more details. -* -* You should have received a copy of the GNU General Public License -* along with Coccinelle. If not, see . -* -* The authors reserve the right to distribute this or future versions of -* Coccinelle under other licenses. -*) + * 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. + * + * Coccinelle is free software: you can redistribute it and/or modify + * it under the terms of the GNU General Public License as published by + * the Free Software Foundation, according to version 2 of the License. + * + * Coccinelle is distributed in the hope that it will be useful, + * but WITHOUT ANY WARRANTY; without even the implied warranty of + * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + * GNU General Public License for more details. + * + * You should have received a copy of the GNU General Public License + * along with Coccinelle. If not, see . + * + * The authors reserve the right to distribute this or future versions of + * Coccinelle under other licenses. + *) module Ast = Ast_cocci @@ -35,21 +37,31 @@ let default_token_info = (* MIXED is like CONTEXT, since sometimes MIXED things have to revert to CONTEXT - see insert_plus.ml *) +type count = ONE (* + *) | MANY (* ++ *) + type mcodekind = MINUS of (Ast.anything list list * token_info) ref - | PLUS + | PLUS of Ast.count | CONTEXT of (Ast.anything Ast.befaft * token_info * token_info) ref | MIXED of (Ast.anything Ast.befaft * token_info * token_info) ref -type info = { line_start : int; line_end : int; - logical_start : int; logical_end : int; +type position_info = { line_start : int; line_end : int; + logical_start : int; logical_end : int; + column : int; offset : int; } + +type info = { pos_info : position_info; attachable_start : bool; attachable_end : bool; mcode_start : mcodekind list; mcode_end : mcodekind list; - column : int; offset : int; (* the following are only for + code *) - strings_before : string list; strings_after : string list } - -type 'a mcode = 'a * arity * info * mcodekind * meta_pos ref (* pos, - only *) + strings_before : (Ast.added_string * position_info) list; + strings_after : (Ast.added_string * position_info) list } + +(* adjacency index is incremented when we skip over dots or nest delimiters +it is used in deciding how much to remove, when two adjacent code tokens are +removed. *) +type 'a mcode = + 'a * arity * info * mcodekind * meta_pos ref (* pos, - only *) * + int (* adjacency_index *) (* int ref is an index *) and 'a wrap = { node : 'a; @@ -90,10 +102,10 @@ and 'a dots = 'a base_dots wrap (* Identifier *) and base_ident = - Id of string mcode - | MetaId of Ast.meta_name mcode * ident list * pure - | MetaFunc of Ast.meta_name mcode * ident list * pure - | MetaLocalFunc of Ast.meta_name mcode * ident list * pure + Id of string mcode + | MetaId of Ast.meta_name mcode * Ast.idconstraint * pure + | MetaFunc of Ast.meta_name mcode * Ast.idconstraint * pure + | MetaLocalFunc of Ast.meta_name mcode * Ast.idconstraint * pure | OptIdent of ident | UniqueIdent of ident @@ -102,7 +114,7 @@ and ident = base_ident wrap (* --------------------------------------------------------------------- *) (* Expression *) -and base_expression = +and base_expression = Ident of ident | Constant of Ast.constant mcode | FunCall of expression * string mcode (* ( *) * @@ -128,8 +140,8 @@ and base_expression = | SizeOfType of string mcode (* sizeof *) * string mcode (* ( *) * typeC * string mcode (* ) *) | TypeExp of typeC (* type name used as an expression, only in args *) - | MetaErr of Ast.meta_name mcode * expression list * pure - | MetaExpr of Ast.meta_name mcode * expression list * + | MetaErr of Ast.meta_name mcode * constraints * pure + | MetaExpr of Ast.meta_name mcode * constraints * Type_cocci.typeC list option * Ast.form * pure | MetaExprList of Ast.meta_name mcode (* only in arg lists *) * listlen * pure @@ -146,15 +158,21 @@ and base_expression = and expression = base_expression wrap +and constraints = + NoConstraint + | NotIdCstrt of Ast.reconstraint + | NotExpCstrt of expression list + | SubExpCstrt of Ast.meta_name list + and listlen = Ast.meta_name mcode option (* --------------------------------------------------------------------- *) (* Types *) -and base_typeC = +and base_typeC = ConstVol of Ast.const_vol mcode * typeC - | BaseType of Ast.baseType mcode * Ast.sign mcode option - | ImplicitInt of Ast.sign mcode + | BaseType of Ast.baseType * string mcode list + | Signed of Ast.sign mcode * typeC option | Pointer of typeC * string mcode (* * *) | FunctionPointer of typeC * string mcode(* ( *)*string mcode(* * *)*string mcode(* ) *)* @@ -164,6 +182,7 @@ and base_typeC = string mcode (* ) *) | Array of typeC * string mcode (* [ *) * expression option * string mcode (* ] *) + | EnumName of string mcode (*enum*) * ident (* name *) | StructUnionName of Ast.structUnion mcode * ident option (* name *) | StructUnionDef of typeC (* either StructUnionName or metavar *) * string mcode (* { *) * declaration dots * string mcode (* } *) @@ -202,24 +221,26 @@ and declaration = base_declaration wrap (* Initializers *) and base_initialiser = - InitExpr of expression + MetaInit of Ast.meta_name mcode * pure + | InitExpr of expression | InitList of string mcode (*{*) * initialiser_list * string mcode (*}*) - | InitGccDotName of - string mcode (*.*) * ident (* name *) * string mcode (*=*) * + | InitGccExt of + designator list (* name *) * string mcode (*=*) * initialiser (* gccext: *) | InitGccName of ident (* name *) * string mcode (*:*) * initialiser - | InitGccIndex of - string mcode (*[*) * expression * string mcode (*]*) * - string mcode (*=*) * initialiser - | InitGccRange of - string mcode (*[*) * expression * string mcode (*...*) * - expression * string mcode (*]*) * string mcode (*=*) * initialiser | IComma of string mcode (* , *) | Idots of string mcode (* ... *) * initialiser option (* whencode *) | OptIni of initialiser | UniqueIni of initialiser +and designator = + DesignatorField of string mcode (* . *) * ident + | DesignatorIndex of string mcode (* [ *) * expression * string mcode (* ] *) + | DesignatorRange of + string mcode (* [ *) * expression * string mcode (* ... *) * + expression * string mcode (* ] *) + and initialiser = base_initialiser wrap and initialiser_list = initialiser dots @@ -293,6 +314,7 @@ and base_statement = statement * (info * mcodekind) (* after info *) | Switch of string mcode (* switch *) * string mcode (* ( *) * expression * string mcode (* ) *) * string mcode (* { *) * + statement (*decl*) dots * case_line dots * string mcode (* } *) | Break of string mcode (* break *) * string mcode (* ; *) | Continue of string mcode (* continue *) * string mcode (* ; *) @@ -306,6 +328,7 @@ and base_statement = | Exp of expression (* only in dotted statement lists *) | TopExp of expression (* for macros body *) | Ty of typeC (* only at top level *) + | TopInit of initialiser (* only at top level *) | Disj of string mcode * statement dots list * string mcode list (* the |s *) * string mcode | Nest of string mcode * statement dots * string mcode * @@ -337,6 +360,8 @@ and ('a,'b) whencode = WhenNot of 'a | WhenAlways of 'b | WhenModifier of Ast.when_modifier + | WhenNotTrue of expression + | WhenNotFalse of expression and statement = base_statement wrap @@ -344,6 +369,8 @@ and base_case_line = Default of string mcode (* default *) * string mcode (*:*) * statement dots | Case of string mcode (* case *) * expression * string mcode (*:*) * statement dots + | DisjCase of string mcode * case_line list * + string mcode list (* the |s *) * string mcode | OptCase of case_line and case_line = base_case_line wrap @@ -372,9 +399,13 @@ and parsed_rule = CocciRule of (rule * Ast.metavar list * (string list * string list * Ast.dependency * string * Ast.exists)) * - (rule * Ast.metavar list) - | ScriptRule of - string * Ast.dependency * (string * Ast.meta_name) list * string + (rule * Ast.metavar list) * Ast.ruletype + | ScriptRule of string (* name *) * + string * Ast.dependency * + (Ast.script_meta_name * Ast.meta_name * Ast.metavar) list * + string + | InitialScriptRule of string (* name *) *string * Ast.dependency * string + | FinalScriptRule of string (* name *) *string * Ast.dependency * string (* --------------------------------------------------------------------- *) @@ -397,6 +428,8 @@ and anything = | CaseLineTag of case_line | TopTag of top_level | IsoWhenTag of Ast.when_modifier + | IsoWhenTTag of expression + | IsoWhenFTag of expression | MetaPosTag of meta_pos let dotsExpr x = DotsExprTag x @@ -418,12 +451,16 @@ let top x = TopTag x (* --------------------------------------------------------------------- *) (* Avoid cluttering the parser. Calculated in compute_lines.ml. *) -let default_info _ = (* why is this a function? *) +let pos_info = { line_start = -1; line_end = -1; logical_start = -1; logical_end = -1; + column = -1; offset = -1; } + +let default_info _ = (* why is this a function? *) + { pos_info = pos_info; attachable_start = true; attachable_end = true; mcode_start = []; mcode_end = []; - column = -1; offset = -1; strings_before = []; strings_after = [] } + strings_before = []; strings_after = [] } let default_befaft _ = MIXED(ref (Ast.NOTHING,default_token_info,default_token_info)) @@ -453,23 +490,25 @@ let context_wrap x = true_if_test_exp = false; iso_info = [] } let unwrap x = x.node -let unwrap_mcode (x,_,_,_,_) = x +let unwrap_mcode (x,_,_,_,_,_) = x let rewrap model x = { model with node = x } -let rewrap_mcode (_,arity,info,mcodekind,pos) x = (x,arity,info,mcodekind,pos) +let rewrap_mcode (_,arity,info,mcodekind,pos,adj) x = + (x,arity,info,mcodekind,pos,adj) let copywrap model x = { model with node = x; index = ref !(model.index); mcodekind = ref !(model.mcodekind); exp_ty = ref !(model.exp_ty)} -let get_pos (_,_,_,_,x) = !x -let get_pos_ref (_,_,_,_,x) = x -let set_pos pos (m,arity,info,mcodekind,_) = (m,arity,info,mcodekind,ref pos) +let get_pos (_,_,_,_,x,_) = !x +let get_pos_ref (_,_,_,_,x,_) = x +let set_pos pos (m,arity,info,mcodekind,_,adj) = + (m,arity,info,mcodekind,ref pos,adj) let get_info x = x.info let set_info x info = {x with info = info} -let get_line x = x.info.line_start -let get_line_end x = x.info.line_end +let get_line x = x.info.pos_info.line_start +let get_line_end x = x.info.pos_info.line_end let get_index x = !(x.index) let set_index x i = x.index := i let get_mcodekind x = !(x.mcodekind) -let get_mcode_mcodekind (_,_,_,mcodekind,_) = mcodekind +let get_mcode_mcodekind (_,_,_,mcodekind,_,_) = mcodekind let get_mcodekind_ref x = x.mcodekind let set_mcodekind x mk = x.mcodekind := mk let set_type x t = x.exp_ty := t @@ -484,7 +523,7 @@ let get_test_exp x = x.true_if_test_exp let set_test_exp x = {x with true_if_test_exp = true} let get_iso x = x.iso_info let set_iso x i = if !Flag.track_iso_usage then {x with iso_info = i} else x -let set_mcode_data data (_,ar,info,mc,pos) = (data,ar,info,mc,pos) +let set_mcode_data data (_,ar,info,mc,pos,adj) = (data,ar,info,mc,pos,adj) (* --------------------------------------------------------------------- *) @@ -505,26 +544,38 @@ let undots d = let rec ast0_type_to_type ty = match unwrap ty with ConstVol(cv,ty) -> Type_cocci.ConstVol(const_vol cv,ast0_type_to_type ty) - | BaseType(bty,None) -> - Type_cocci.BaseType(baseType bty,None) - | BaseType(bty,Some sgn) -> - Type_cocci.BaseType(baseType bty,Some (sign sgn)) - | ImplicitInt(sgn) -> - let bty = Type_cocci.IntType in - Type_cocci.BaseType(bty,Some (sign sgn)) + | BaseType(bty,strings) -> + Type_cocci.BaseType(baseType bty) + | Signed(sgn,None) -> + Type_cocci.SignedT(sign sgn,None) + | Signed(sgn,Some ty) -> + let bty = ast0_type_to_type ty in + Type_cocci.SignedT(sign sgn,Some bty) | Pointer(ty,_) -> Type_cocci.Pointer(ast0_type_to_type ty) | FunctionPointer(ty,_,_,_,_,params,_) -> Type_cocci.FunctionPointer(ast0_type_to_type ty) | FunctionType _ -> failwith "not supported" | Array(ety,_,_,_) -> Type_cocci.Array(ast0_type_to_type ety) + | EnumName(su,tag) -> + (match unwrap tag with + Id(tag) -> + Type_cocci.EnumName(false,unwrap_mcode tag) + | MetaId(tag,_,_) -> + (Printf.printf + "warning: enum with a metavariable name detected.\n"; + Printf.printf + "For type checking assuming the name of the metavariable is the name of the type\n"; + let (rule,tag) = unwrap_mcode tag in + Type_cocci.EnumName(true,rule^tag)) + | _ -> failwith "unexpected enum type name") | StructUnionName(su,Some tag) -> (match unwrap tag with Id(tag) -> Type_cocci.StructUnionName(structUnion su,false,unwrap_mcode tag) | MetaId(tag,_,_) -> - (Printf.printf + (Common.pr2 "warning: struct/union with a metavariable name detected.\n"; - Printf.printf + Common.pr2 "For type checking assuming the name of the metavariable is the name of the type\n"; let (rule,tag) = unwrap_mcode tag in Type_cocci.StructUnionName(structUnion su,true,rule^tag)) @@ -534,12 +585,14 @@ let rec ast0_type_to_type ty = | TypeName(name) -> Type_cocci.TypeName(unwrap_mcode name) | MetaType(name,_) -> Type_cocci.MetaType(unwrap_mcode name,Type_cocci.Unitary,false) - | DisjType(_,types,_,_) -> failwith "unexpected DisjType" + | DisjType(_,types,_,_) -> + Common.pr2_once + "disjtype not supported in smpl type inference, assuming unknown"; + Type_cocci.Unknown | OptType(ty) | UniqueType(ty) -> ast0_type_to_type ty -and baseType t = - match unwrap_mcode t with +and baseType = function Ast.VoidType -> Type_cocci.VoidType | Ast.CharType -> Type_cocci.CharType | Ast.ShortType -> Type_cocci.ShortType @@ -547,6 +600,7 @@ and baseType t = | Ast.DoubleType -> Type_cocci.DoubleType | Ast.FloatType -> Type_cocci.FloatType | Ast.LongType -> Type_cocci.LongType + | Ast.LongLongType -> Type_cocci.LongLongType and structUnion t = match unwrap_mcode t with @@ -567,46 +621,61 @@ and const_vol t = (* this function is a rather minimal attempt. the problem is that information has been lost. but since it is only used for metavariable types in the isos, perhaps it doesn't matter *) -let make_mcode x = (x,NONE,default_info(),context_befaft(),ref NoMetaPos) -let make_mcode_info x info = (x,NONE,info,context_befaft(),ref NoMetaPos) +and make_mcode x = (x,NONE,default_info(),context_befaft(),ref NoMetaPos,-1) +let make_mcode_info x info = (x,NONE,info,context_befaft(),ref NoMetaPos,-1) exception TyConv let rec reverse_type ty = match ty with Type_cocci.ConstVol(cv,ty) -> - ConstVol(reverse_const_vol cv,wrap(reverse_type ty)) - | Type_cocci.BaseType(bty,None) -> - BaseType(reverse_baseType bty,None) - | Type_cocci.BaseType(bty,Some sgn) -> - BaseType(reverse_baseType bty,Some (reverse_sign sgn)) + ConstVol(reverse_const_vol cv,context_wrap(reverse_type ty)) + | Type_cocci.BaseType(bty) -> + BaseType(reverse_baseType bty,[(* not used *)]) + | Type_cocci.SignedT(sgn,None) -> Signed(reverse_sign sgn,None) + | Type_cocci.SignedT(sgn,Some bty) -> + Signed(reverse_sign sgn,Some (context_wrap(reverse_type ty))) | Type_cocci.Pointer(ty) -> - Pointer(wrap(reverse_type ty),make_mcode "*") + Pointer(context_wrap(reverse_type ty),make_mcode "*") + | Type_cocci.EnumName(mv,tag) -> + if mv + then + (* not right... *) + let rule = "" in + EnumName + (make_mcode "enum", + context_wrap(MetaId(make_mcode (rule,tag),Ast.IdNoConstraint, + Impure))) + else + EnumName(make_mcode "enum",context_wrap(Id(make_mcode tag))) | Type_cocci.StructUnionName(su,mv,tag) -> if mv then (* not right... *) - StructUnionName(reverse_structUnion su, - Some(wrap(MetaId(make_mcode ("",tag),[],Impure)))) + let rule = "" in + StructUnionName + (reverse_structUnion su, + Some(context_wrap(MetaId(make_mcode (rule,tag),Ast.IdNoConstraint, + Impure)))) else - StructUnionName(reverse_structUnion su, - Some (wrap(Id(make_mcode tag)))) + StructUnionName + (reverse_structUnion su, + Some (context_wrap(Id(make_mcode tag)))) | Type_cocci.TypeName(name) -> TypeName(make_mcode name) | Type_cocci.MetaType(name,_,_) -> MetaType(make_mcode name,Impure(*not really right*)) | _ -> raise TyConv -and reverse_baseType t = - make_mcode - (match t with - Type_cocci.VoidType -> Ast.VoidType - | Type_cocci.CharType -> Ast.CharType - | Type_cocci.BoolType -> Ast.IntType - | Type_cocci.ShortType -> Ast.ShortType - | Type_cocci.IntType -> Ast.IntType - | Type_cocci.DoubleType -> Ast.DoubleType - | Type_cocci.FloatType -> Ast.FloatType - | Type_cocci.LongType -> Ast.LongType) +and reverse_baseType = function + Type_cocci.VoidType -> Ast.VoidType + | Type_cocci.CharType -> Ast.CharType + | Type_cocci.BoolType -> Ast.IntType + | Type_cocci.ShortType -> Ast.ShortType + | Type_cocci.IntType -> Ast.IntType + | Type_cocci.DoubleType -> Ast.DoubleType + | Type_cocci.FloatType -> Ast.FloatType + | Type_cocci.LongType -> Ast.LongType + | Type_cocci.LongLongType -> Ast.LongLongType and reverse_structUnion t = make_mcode