package coccinelle

  1. Overview
  2. Docs
type added_string = Ast_cocci.added_string =
  1. | Noindent of string
  2. | Indent of string
  3. | Space of string
type info = Ast_cocci.info = {
  1. line : int;
  2. column : int;
  3. strbef : (added_string * int * int) list;
  4. straft : (added_string * int * int) list;
  5. whitespace : string;
}
type line = int
type meta_name = string * string
type script_position = string * line
type !'a wrap = 'a Ast_cocci.wrap = {
  1. node : 'a;
  2. node_line : line;
  3. free_vars : meta_name list;
  4. minus_free_vars : meta_name list;
  5. minus_nc_free_vars : meta_name list;
  6. fresh_vars : (meta_name * seed) list;
  7. inherited : meta_name list;
  8. positive_inherited_positions : meta_name list;
  9. constraints : (meta_name * constraints) list;
  10. saved_witness : meta_name list;
  11. bef_aft : dots_bef_aft;
  12. pos_info : meta_name mcode option;
  13. true_if_test_exp : bool;
  14. safe_for_multi_decls : safety;
  15. iso_info : (string * anything) list;
}
and !'a befaft = 'a Ast_cocci.befaft =
  1. | BEFORE of 'a list list * count
  2. | AFTER of 'a list list * count
  3. | BEFOREAFTER of 'a list list * 'a list list * count
  4. | NOTHING
and !'a replacement = 'a Ast_cocci.replacement =
  1. | REPLACEMENT of 'a list list * count
  2. | NOREPLACEMENT
and !'a mcode = 'a * info * mcodekind * meta_pos list
and adjacency = Ast_cocci.adjacency =
  1. | ALLMINUS
  2. | ADJ of int
and mcodekind = Ast_cocci.mcodekind =
  1. | MINUS of pos * int list * adjacency * anything replacement
  2. | CONTEXT of pos * anything befaft
  3. | PLUS of count
and count = Ast_cocci.count =
  1. | ONE
  2. | MANY
and fixpos = Ast_cocci.fixpos =
  1. | Real of int
  2. | Virt of int * int
and pos = Ast_cocci.pos =
  1. | NoPos
  2. | DontCarePos
  3. | FixPos of fixpos * fixpos
and dots_bef_aft = Ast_cocci.dots_bef_aft =
  1. | NoDots
  2. | AddingBetweenDots of statement * int
  3. | DroppingBetweenDots of statement * int
and inherited = bool
and keep_binding = Ast_cocci.keep_binding =
  1. | Unitary
  2. | Nonunitary
  3. | Saved
and multi = bool
and end_info = meta_name list * (meta_name * seed) list * meta_name list * mcodekind
and safety = Ast_cocci.safety =
  1. | Safe
  2. | Unsafe
  3. | NoStorage
and arity = Ast_cocci.arity =
  1. | UNIQUE
  2. | OPT
  3. | MULTI
  4. | NONE
and metavar = Ast_cocci.metavar =
  1. | MetaMetaDecl of arity * meta_name
  2. | MetaIdDecl of arity * meta_name
  3. | MetaFreshIdDecl of meta_name * seed
  4. | MetaTypeDecl of arity * meta_name
  5. | MetaInitDecl of arity * meta_name
  6. | MetaInitListDecl of arity * meta_name * list_len
  7. | MetaListlenDecl of meta_name
  8. | MetaParamDecl of arity * meta_name
  9. | MetaParamListDecl of arity * meta_name * list_len
  10. | MetaBinaryOperatorDecl of arity * meta_name
  11. | MetaAssignmentOperatorDecl of arity * meta_name
  12. | MetaConstDecl of arity * meta_name * fullType list option
  13. | MetaErrDecl of arity * meta_name
  14. | MetaExpDecl of arity * meta_name * fullType list option * list_len option
  15. | MetaIdExpDecl of arity * meta_name * fullType list option
  16. | MetaLocalIdExpDecl of arity * meta_name * fullType list option
  17. | MetaGlobalIdExpDecl of arity * meta_name * fullType list option
  18. | MetaExpListDecl of arity * meta_name * list_len
  19. | MetaDeclDecl of arity * meta_name
  20. | MetaFieldDecl of arity * meta_name
  21. | MetaFieldListDecl of arity * meta_name * list_len
  22. | MetaStmDecl of arity * meta_name
  23. | MetaStmListDecl of arity * meta_name * list_len
  24. | MetaDParamListDecl of arity * meta_name * list_len
  25. | MetaFuncDecl of arity * meta_name
  26. | MetaLocalFuncDecl of arity * meta_name
  27. | MetaPosDecl of arity * meta_name
  28. | MetaComDecl of arity * meta_name
  29. | MetaFmtDecl of arity * meta_name
  30. | MetaAttributeDecl of arity * meta_name
  31. | MetaFragListDecl of arity * meta_name * list_len
  32. | MetaAnalysisDecl of string * meta_name
  33. | MetaDeclarerDecl of arity * meta_name
  34. | MetaIteratorDecl of arity * meta_name
  35. | MetaScriptDecl of metavar option ref * meta_name
and list_len = Ast_cocci.list_len =
  1. | AnyLen
  2. | MetaLen of meta_name * constraints
  3. | CstLen of int
and seed = Ast_cocci.seed =
  1. | NoVal
  2. | StringSeed of string
  3. | ListSeed of seed_elem list
  4. | ScriptSeed of seed_script
and seed_elem = Ast_cocci.seed_elem =
  1. | SeedString of string
  2. | SeedId of meta_name
and seed_script = string * string * (meta_name * metavar) list * script_position * string
and !'a dots = 'a list wrap
and base_ident = Ast_cocci.base_ident =
  1. | Id of string mcode
  2. | MetaId of meta_name mcode * constraints * keep_binding * inherited
  3. | MetaFunc of meta_name mcode * constraints * keep_binding * inherited
  4. | MetaLocalFunc of meta_name mcode * constraints * keep_binding * inherited
  5. | AsIdent of ident * ident
  6. | DisjId of ident list
  7. | ConjId of ident list
  8. | OptIdent of ident
and ident = base_ident wrap
and base_expression = Ast_cocci.base_expression =
  1. | Ident of ident
  2. | Constant of constant mcode
  3. | StringConstant of string mcode * string_fragment dots * string mcode * isWchar
  4. | FunCall of expression * string mcode * expression dots * string mcode
  5. | Assignment of expression * assignOp * expression * bool
  6. | Sequence of expression * string mcode * expression
  7. | CondExpr of expression * string mcode * expression option * string mcode * expression
  8. | Postfix of expression * fixOp mcode
  9. | Infix of expression * fixOp mcode
  10. | Unary of expression * unaryOp mcode
  11. | Binary of expression * binaryOp * expression
  12. | Nested of expression * binaryOp * expression
  13. | ArrayAccess of expression * string mcode * expression * string mcode
  14. | RecordAccess of expression * string mcode * ident
  15. | RecordPtAccess of expression * string mcode * ident
  16. | Cast of string mcode * fullType * attr list * string mcode * expression
  17. | SizeOfExpr of string mcode * expression
  18. | SizeOfType of string mcode * string mcode * fullType * string mcode
  19. | TypeExp of fullType
  20. | Paren of string mcode * expression * string mcode
  21. | Constructor of string mcode * fullType * string mcode * initialiser
  22. | MetaErr of meta_name mcode * constraints * keep_binding * inherited
  23. | MetaExpr of meta_name mcode * constraints * keep_binding * fullType list option * form * inherited * listlen option
  24. | MetaExprList of meta_name mcode * listlen * constraints * keep_binding * inherited
  25. | AsExpr of expression * expression
  26. | AsSExpr of expression * rule_elem
  27. | EComma of string mcode
  28. | DisjExpr of expression list
  29. | ConjExpr of expression list
  30. | NestExpr of string mcode * expression dots * string mcode * expression option * multi
  31. | Edots of string mcode * expression option
  32. | OptExp of expression
and !'expression generic_constraints = 'expression Ast_cocci.generic_constraints =
  1. | CstrFalse
  2. | CstrTrue
  3. | CstrAnd of 'expression generic_constraints list
  4. | CstrOr of 'expression generic_constraints list
  5. | CstrNot of 'expression generic_constraints
  6. | CstrConstant of constant_constraint
  7. | CstrOperator of operator_constraint
  8. | CstrMeta_name of meta_name
  9. | CstrRegexp of string * Regexp.regexp
  10. | CstrScript of bool * script_constraint
  11. | CstrExpr of 'expression
  12. | CstrSub of meta_name list
  13. | CstrType of fullType
and constant_constraint = Ast_cocci.constant_constraint =
  1. | CstrInt of int_constraint
  2. | CstrString of string
and int_constraint = Ast_cocci.int_constraint =
  1. | CstrIntEq of string
  2. | CstrIntLeq of int
  3. | CstrIntGeq of int
and operator_constraint = Ast_cocci.operator_constraint =
  1. | CstrAssignOp of assignOp
  2. | CstrBinaryOp of binaryOp
and script_constraint = string * string * (meta_name * metavar) list * script_position * string
and form = Ast_cocci.form =
  1. | ANY
  2. | ID
  3. | LocalID
  4. | GlobalID
  5. | CONST
and expression = base_expression wrap
and listlen = Ast_cocci.listlen =
  1. | MetaListLen of meta_name mcode * constraints * keep_binding * inherited
  2. | CstListLen of int
  3. | AnyListLen
and base_string_fragment = Ast_cocci.base_string_fragment =
  1. | ConstantFragment of string mcode
  2. | FormatFragment of string mcode * string_format
  3. | Strdots of string mcode
  4. | MetaFormatList of string mcode * meta_name mcode * listlen * constraints * keep_binding * inherited
and string_fragment = base_string_fragment wrap
and base_string_format = Ast_cocci.base_string_format =
  1. | ConstantFormat of string mcode
  2. | MetaFormat of meta_name mcode * constraints * keep_binding * inherited
and string_format = base_string_format wrap
and unaryOp = Ast_cocci.unaryOp =
  1. | GetRef
  2. | GetRefLabel
  3. | DeRef
  4. | UnPlus
  5. | UnMinus
  6. | Tilde
  7. | Not
and base_assignOp = Ast_cocci.base_assignOp =
  1. | SimpleAssign of simpleAssignOp mcode
  2. | OpAssign of arithOp mcode
  3. | MetaAssign of meta_name mcode * constraints * keep_binding * inherited
and simpleAssignOp = string
and assignOp = base_assignOp wrap
and fixOp = Ast_cocci.fixOp =
  1. | Dec
  2. | Inc
and base_binaryOp = Ast_cocci.base_binaryOp =
  1. | Arith of arithOp mcode
  2. | Logical of logicalOp mcode
  3. | MetaBinary of meta_name mcode * constraints * keep_binding * inherited
and binaryOp = base_binaryOp wrap
and arithOp = Ast_cocci.arithOp =
  1. | Plus
  2. | Minus
  3. | Mul
  4. | Div
  5. | Mod
  6. | DecLeft
  7. | DecRight
  8. | And
  9. | Or
  10. | Xor
  11. | Min
  12. | Max
and logicalOp = Ast_cocci.logicalOp =
  1. | Inf
  2. | Sup
  3. | InfEq
  4. | SupEq
  5. | Eq
  6. | NotEq
  7. | AndLog
  8. | OrLog
and constant = Ast_cocci.constant =
  1. | String of string * isWchar
  2. | Char of string * isWchar
  3. | Int of string
  4. | Float of string
  5. | DecimalConst of string * string * string
and isWchar = Ast_cocci.isWchar =
  1. | IsWchar
  2. | IsUchar
  3. | Isuchar
  4. | Isu8char
  5. | IsChar
and base_fullType = Ast_cocci.base_fullType =
  1. | Type of bool * const_vol mcode list * typeC
  2. | AsType of fullType * fullType
  3. | DisjType of fullType list
  4. | ConjType of fullType list
  5. | OptType of fullType
and base_typeC = Ast_cocci.base_typeC =
  1. | BaseType of baseType * string mcode list
  2. | SignedT of sign mcode * typeC option
  3. | Pointer of fullType * string mcode
  4. | ParenType of string mcode * fullType * string mcode
  5. | FunctionType of fullType * string mcode * parameter_list * string mcode
  6. | Array of fullType * string mcode * expression option * string mcode
  7. | Decimal of string mcode * string mcode * expression * string mcode option * expression option * string mcode
  8. | EnumName of string mcode * ident option
  9. | EnumDef of fullType * string mcode * enum_decl dots * string mcode
  10. | StructUnionName of structUnion mcode * ident option
  11. | StructUnionDef of fullType * string mcode * annotated_field dots * string mcode
  12. | TypeOfExpr of string mcode * string mcode * expression * string mcode
  13. | TypeOfType of string mcode * string mcode * fullType * string mcode
  14. | TypeName of string mcode
  15. | AutoType of string mcode
  16. | MetaType of meta_name mcode * constraints * keep_binding * inherited
and fullType = base_fullType wrap
and typeC = base_typeC wrap
and baseType = Ast_cocci.baseType =
  1. | VoidType
  2. | CharType
  3. | ShortType
  4. | ShortIntType
  5. | IntType
  6. | DoubleType
  7. | LongDoubleType
  8. | FloatType
  9. | LongDoubleComplexType
  10. | DoubleComplexType
  11. | FloatComplexType
  12. | LongType
  13. | LongIntType
  14. | LongLongType
  15. | LongLongIntType
  16. | SizeType
  17. | SSizeType
  18. | PtrDiffType
  19. | BoolType
  20. | Unknown
and structUnion = Ast_cocci.structUnion =
  1. | Struct
  2. | Union
and sign = Ast_cocci.sign =
  1. | Signed
  2. | Unsigned
and const_vol = Ast_cocci.const_vol =
  1. | Const
  2. | Volatile
and base_declaration = Ast_cocci.base_declaration =
  1. | Init of storage mcode option * fullType * attr list * ident * attr list * string mcode * initialiser * string mcode
  2. | UnInit of storage mcode option * fullType * attr list * ident * attr list * string mcode
  3. | FunProto of fninfo list * attr list * ident * string mcode * parameter_list * (string mcode * string mcode) option * string mcode * string mcode
  4. | TyDecl of fullType * attr list * string mcode
  5. | MacroDecl of storage mcode option * ident * string mcode * expression dots * string mcode * attr list * string mcode
  6. | MacroDeclInit of storage mcode option * ident * string mcode * expression dots * string mcode * string mcode * initialiser * string mcode
  7. | Typedef of string mcode * fullType * typeC * string mcode
  8. | DisjDecl of declaration list
  9. | ConjDecl of declaration list
  10. | MetaDecl of meta_name mcode * constraints * keep_binding * inherited
  11. | AsDecl of declaration * declaration
  12. | OptDecl of declaration
and declaration = base_declaration wrap
and base_annotated_decl = Ast_cocci.base_annotated_decl =
  1. | DElem of mcodekind * bool * declaration
and annotated_decl = base_annotated_decl wrap
and base_field = Ast_cocci.base_field =
  1. | Field of fullType * ident option * bitfield option * string mcode
  2. | MetaField of meta_name mcode * constraints * keep_binding * inherited
  3. | MetaFieldList of meta_name mcode * listlen * constraints * keep_binding * inherited
and bitfield = string mcode * expression
and field = base_field wrap
and base_annotated_field = Ast_cocci.base_annotated_field =
  1. | FElem of mcodekind * bool * field
  2. | Fdots of string mcode * field option
  3. | DisjField of annotated_field list
  4. | ConjField of annotated_field list
  5. | OptField of annotated_field
and annotated_field = base_annotated_field wrap
and base_enum_decl = Ast_cocci.base_enum_decl =
  1. | Enum of ident * (string mcode * expression) option
  2. | EnumComma of string mcode
  3. | EnumDots of string mcode * enum_decl option
and enum_decl = base_enum_decl wrap
and base_initialiser = Ast_cocci.base_initialiser =
  1. | MetaInit of meta_name mcode * constraints * keep_binding * inherited
  2. | MetaInitList of meta_name mcode * listlen * constraints * keep_binding * inherited
  3. | AsInit of initialiser * initialiser
  4. | InitExpr of expression
  5. | ArInitList of string mcode * initialiser dots * string mcode
  6. | StrInitList of bool * string mcode * initialiser list * string mcode * initialiser list
  7. | InitGccExt of designator list * string mcode * initialiser
  8. | InitGccName of ident * string mcode * initialiser
  9. | IComma of string mcode
  10. | Idots of string mcode * initialiser option
  11. | OptIni of initialiser
and designator = Ast_cocci.designator =
  1. | DesignatorField of string mcode * ident
  2. | DesignatorIndex of string mcode * expression * string mcode
  3. | DesignatorRange of string mcode * expression * string mcode * expression * string mcode
and initialiser = base_initialiser wrap
and base_parameterTypeDef = Ast_cocci.base_parameterTypeDef =
  1. | VoidParam of fullType * attr list
  2. | Param of fullType * attr list * ident option * attr list
  3. | MetaParam of meta_name mcode * constraints * keep_binding * inherited
  4. | MetaParamList of meta_name mcode * listlen * constraints * keep_binding * inherited
  5. | AsParam of parameterTypeDef * expression
  6. | PComma of string mcode
  7. | Pdots of string mcode
  8. | OptParam of parameterTypeDef
and parameterTypeDef = base_parameterTypeDef wrap
and parameter_list = parameterTypeDef dots
and base_define_param = Ast_cocci.base_define_param =
  1. | DParam of ident
  2. | MetaDParamList of meta_name mcode * listlen * constraints * keep_binding * inherited
  3. | DPComma of string mcode
  4. | DPdots of string mcode
  5. | OptDParam of define_param
and define_param = base_define_param wrap
and base_define_parameters = Ast_cocci.base_define_parameters =
  1. | NoParams
  2. | DParams of string mcode * define_param dots * string mcode
and define_parameters = base_define_parameters wrap
and meta_collect = Ast_cocci.meta_collect =
  1. | PER
  2. | ALL
and storage = Ast_cocci.storage =
  1. | Static
  2. | Auto
  3. | Register
  4. | Extern
and base_rule_elem = Ast_cocci.base_rule_elem =
  1. | FunHeader of mcodekind * bool * fninfo list * ident * string mcode * parameter_list * (string mcode * string mcode) option * string mcode * attr list
  2. | Decl of annotated_decl
  3. | SeqStart of string mcode
  4. | SeqEnd of string mcode
  5. | ExprStatement of expression option * string mcode
  6. | IfHeader of string mcode * string mcode * expression * string mcode
  7. | Else of string mcode
  8. | WhileHeader of string mcode * string mcode * expression * string mcode
  9. | DoHeader of string mcode
  10. | WhileTail of string mcode * string mcode * expression * string mcode * string mcode
  11. | ForHeader of string mcode * string mcode * forinfo * expression option * string mcode * expression option * string mcode
  12. | IteratorHeader of ident * string mcode * expression dots * string mcode
  13. | SwitchHeader of string mcode * string mcode * expression * string mcode
  14. | Break of string mcode * string mcode
  15. | Continue of string mcode * string mcode
  16. | Label of ident * string mcode
  17. | Goto of string mcode * ident * string mcode
  18. | Return of string mcode * string mcode
  19. | ReturnExpr of string mcode * expression * string mcode
  20. | Exec of string mcode * string mcode * exec_code dots * string mcode
  21. | MetaRuleElem of meta_name mcode * constraints * keep_binding * inherited
  22. | MetaStmt of meta_name mcode * constraints * keep_binding * metaStmtInfo * inherited
  23. | MetaStmtList of meta_name mcode * listlen * constraints * keep_binding * inherited
  24. | Exp of expression
  25. | TopExp of expression
  26. | Ty of fullType
  27. | TopId of ident
  28. | TopInit of initialiser
  29. | Include of string mcode * inc_file mcode
  30. | MetaInclude of string mcode * expression
  31. | Undef of string mcode * ident
  32. | DefineHeader of string mcode * ident * define_parameters
  33. | Pragma of string mcode * ident * pragmainfo
  34. | Case of string mcode * expression * string mcode
  35. | Default of string mcode * string mcode
  36. | AsRe of rule_elem * rule_elem
  37. | DisjRuleElem of rule_elem list
and base_pragmainfo = Ast_cocci.base_pragmainfo =
  1. | PragmaString of string mcode
  2. | PragmaDots of string mcode
and pragmainfo = base_pragmainfo wrap
and forinfo = Ast_cocci.forinfo =
  1. | ForExp of expression option * string mcode
  2. | ForDecl of annotated_decl
and fninfo = Ast_cocci.fninfo =
  1. | FStorage of storage mcode
  2. | FType of fullType
  3. | FInline of string mcode
  4. | FAttr of attr
and base_attr = Ast_cocci.base_attr =
  1. | Attribute of attr_arg
  2. | GccAttribute of string mcode * string mcode * string mcode * attr_arg * string mcode * string mcode
and attr = base_attr wrap
and base_attr_arg = Ast_cocci.base_attr_arg =
  1. | MacroAttr of string mcode
  2. | MacroAttrArgs of string mcode * string mcode * expression dots * string mcode
  3. | MetaAttr of meta_name mcode * constraints * keep_binding * inherited
and attr_arg = base_attr_arg wrap
and metaStmtInfo = Ast_cocci.metaStmtInfo =
  1. | NotSequencible
  2. | SequencibleAfterDots of dots_whencode list
  3. | Sequencible
and rule_elem = base_rule_elem wrap
and base_statement = Ast_cocci.base_statement =
  1. | Seq of rule_elem * statement dots * rule_elem
  2. | IfThen of rule_elem * statement * end_info
  3. | IfThenElse of rule_elem * statement * rule_elem * statement * end_info
  4. | While of rule_elem * statement * end_info
  5. | Do of rule_elem * statement * rule_elem
  6. | For of rule_elem * statement * end_info
  7. | Iterator of rule_elem * statement * end_info
  8. | Switch of rule_elem * rule_elem * statement dots * case_line list * rule_elem
  9. | Atomic of rule_elem
  10. | Disj of statement dots list
  11. | Conj of statement dots list
  12. | Nest of string mcode * statement dots * string mcode * (statement dots, statement) whencode list * multi * dots_whencode list * dots_whencode list
  13. | FunDecl of rule_elem * rule_elem * statement dots * rule_elem * end_info
  14. | Define of rule_elem * statement dots
  15. | AsStmt of statement * statement
  16. | Dots of string mcode * (statement dots, statement) whencode list * dots_whencode list * dots_whencode list
  17. | OptStm of statement
and (!'a, !'b) whencode = ('a, 'b) Ast_cocci.whencode =
  1. | WhenNot of 'a
  2. | WhenAlways of 'b
  3. | WhenModifier of when_modifier
  4. | WhenNotTrue of rule_elem
  5. | WhenNotFalse of rule_elem
and when_modifier = Ast_cocci.when_modifier =
  1. | WhenAny
  2. | WhenStrict
  3. | WhenForall
  4. | WhenExists
and dots_whencode = Ast_cocci.dots_whencode =
  1. | WParen of rule_elem * meta_name
  2. | Other of statement
  3. | Other_dots of statement dots
and statement = base_statement wrap
and base_case_line = Ast_cocci.base_case_line =
  1. | CaseLine of rule_elem * statement dots
  2. | OptCase of case_line
and case_line = base_case_line wrap
and base_exec_code = Ast_cocci.base_exec_code =
  1. | ExecEval of string mcode * expression
  2. | ExecToken of string mcode
  3. | ExecDots of string mcode
and exec_code = base_exec_code wrap
and inc_file = Ast_cocci.inc_file =
  1. | Local of inc_elem list
  2. | NonLocal of inc_elem list
  3. | AnyInc
and inc_elem = Ast_cocci.inc_elem =
  1. | IncPath of string
  2. | IncDots
and base_top_level = Ast_cocci.base_top_level =
  1. | NONDECL of statement
  2. | CODE of statement dots
  3. | FILEINFO of string mcode * string mcode
  4. | ERRORWORDS of expression list
and top_level = base_top_level wrap
and parser_kind = Ast_cocci.parser_kind =
  1. | ExpP
  2. | IdP
  3. | TyP
  4. | AnyP
and rulename = Ast_cocci.rulename =
  1. | CocciRulename of string option * dependency * string list * string list * exists * parser_kind
  2. | GeneratedRulename of string option * dependency * string list * string list * exists * parser_kind
  3. | ScriptRulename of string option * string * dependency
  4. | InitialScriptRulename of string option * string * dependency
  5. | FinalScriptRulename of string option * string * dependency
and ruletype = Ast_cocci.ruletype =
  1. | Normal
  2. | Generated
and rule = Ast_cocci.rule =
  1. | CocciRule of string * dependency * string list * exists * top_level list * bool list * ruletype
  2. | ScriptRule of string * string * dependency * (script_meta_name * meta_name * metavar * mvinit) list * meta_name list * script_position * string
  3. | InitialScriptRule of string * string * dependency * (script_meta_name * meta_name * metavar * mvinit) list * script_position * string
  4. | FinalScriptRule of string * string * dependency * (script_meta_name * meta_name * metavar * mvinit) list * script_position * string
and script_meta_name = string option * string option
and mvinit = Ast_cocci.mvinit =
  1. | NoMVInit
  2. | MVInitString of string
  3. | MVInitPosList
and dep = Ast_cocci.dep =
  1. | Dep of string
  2. | AntiDep of string
  3. | EverDep of string
  4. | NeverDep of string
  5. | AndDep of dep * dep
  6. | OrDep of dep * dep
  7. | FileIn of string
  8. | NotFileIn of string
and dependency = Ast_cocci.dependency =
  1. | NoDep
  2. | FailDep
  3. | ExistsDep of dep
  4. | ForallDep of dep
and rule_with_metavars = metavar list * rule
and anything = Ast_cocci.anything =
  1. | FullTypeTag of fullType
  2. | BaseTypeTag of baseType
  3. | StructUnionTag of structUnion
  4. | SignTag of sign
  5. | IdentTag of ident
  6. | ExpressionTag of expression
  7. | ConstantTag of constant
  8. | UnaryOpTag of unaryOp
  9. | AssignOpTag of assignOp
  10. | SimpleAssignOpTag of simpleAssignOp
  11. | OpAssignOpTag of arithOp
  12. | FixOpTag of fixOp
  13. | BinaryOpTag of binaryOp
  14. | ArithOpTag of arithOp
  15. | LogicalOpTag of logicalOp
  16. | DeclarationTag of declaration
  17. | FieldTag of field
  18. | EnumDeclTag of enum_decl
  19. | InitTag of initialiser
  20. | StorageTag of storage
  21. | IncFileTag of inc_file
  22. | Rule_elemTag of rule_elem
  23. | StatementTag of statement
  24. | ForInfoTag of forinfo
  25. | CaseLineTag of case_line
  26. | StringFragmentTag of string_fragment
  27. | AttributeTag of attr
  28. | AttrArgTag of attr_arg
  29. | ConstVolTag of const_vol
  30. | Token of string * info option
  31. | Directive of added_string list
  32. | Code of top_level
  33. | ExprDotsTag of expression dots
  34. | ParamDotsTag of parameterTypeDef dots
  35. | StmtDotsTag of statement dots
  36. | AnnDeclDotsTag of annotated_decl dots
  37. | AnnFieldDotsTag of annotated_field dots
  38. | EnumDeclDotsTag of enum_decl dots
  39. | DefParDotsTag of define_param dots
  40. | TypeCTag of typeC
  41. | ParamTag of parameterTypeDef
  42. | SgrepStartTag of string
  43. | SgrepEndTag of string
and exists = Ast_cocci.exists =
  1. | Exists
  2. | Forall
  3. | Undetermined
val mkToken : string -> anything
val lub_count : count -> count -> count
val rewrap : 'a wrap -> 'b -> 'b wrap
val rewrap_mcode : 'a mcode -> 'b -> 'b mcode
val unwrap : 'a wrap -> 'a
val unwrap_mcode : 'a mcode -> 'a
val get_mcodekind : 'a mcode -> mcodekind
val get_line : 'a wrap -> line
val get_mcode_line : 'a mcode -> line
val get_mcode_col : 'a mcode -> int
val get_fvs : 'a wrap -> meta_name list
val get_wcfvs : ('a wrap, 'b wrap) whencode list -> meta_name list
val set_fvs : meta_name list -> 'a wrap -> 'a wrap
val get_mfvs : 'a wrap -> meta_name list
val set_mfvs : meta_name list -> 'a wrap -> 'a wrap
val get_minus_nc_fvs : 'a wrap -> meta_name list
val get_fresh : 'a wrap -> (meta_name * seed) list
val get_inherited : 'a wrap -> meta_name list
val get_inherited_pos : 'a wrap -> meta_name list
val get_constraints : 'a wrap -> (meta_name * constraints) list
val add_constraint : 'a wrap -> (meta_name * constraints) -> 'a wrap
val get_saved : 'a wrap -> meta_name list
val get_dots_bef_aft : statement -> dots_bef_aft
val set_dots_bef_aft : dots_bef_aft -> statement -> statement
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 -> safety
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 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
val tag2c : anything -> string
val no_info : info
val make_meta_rule_elem : string -> mcodekind -> constraints -> (meta_name list * (meta_name * seed) list * meta_name list) -> rule_elem
val make_meta_decl : string -> mcodekind -> constraints -> (meta_name list * (meta_name * seed) list * meta_name list) -> declaration
val make_term : 'a -> 'a wrap
val make_inherited_term : 'a -> meta_name list -> meta_name list -> 'a wrap
val make_mcode : 'a -> 'a mcode
val equal_pos : fixpos -> fixpos -> bool
val string_of_arithOp : arithOp -> string
val string_of_logicalOp : logicalOp -> string
val string_of_assignOp : assignOp -> string
val string_of_binaryOp : binaryOp -> string
val string_of_sign : sign -> string
val string_of_baseType : baseType -> string
val string_of_const_vol : const_vol list -> string
val string_of_structUnion : structUnion -> string
val string_of_typeC : typeC -> string
val string_of_fullType : fullType -> string
val typeC_of_fullType_opt : fullType -> typeC option
val ident_of_expression_opt : expression -> ident option
val string_of_meta_name : meta_name -> string
type !'a transformer = 'a Ast_cocci.transformer = {
  1. baseType : (baseType -> string mcode list -> 'a) option;
  2. decimal : (string mcode -> string mcode -> expression -> string mcode option -> expression option -> string mcode -> 'a) option;
  3. enumName : (string mcode -> ident option -> 'a) option;
  4. structUnionName : (structUnion mcode -> ident option -> 'a) option;
  5. typeName : (string mcode -> 'a) option;
  6. metaType : (meta_name mcode -> constraints -> keep_binding -> inherited -> 'a) option;
}
val empty_transformer : 'a transformer
val fullType_map : base_typeC transformer -> fullType -> fullType
val fullType_fold : ('a -> 'a) transformer -> fullType -> 'a -> 'a
val fullType_iter : unit transformer -> fullType -> unit
val meta_names_of_fullType : fullType -> meta_name list
val string_of_expression : expression -> string option
type (!'expression, !'a) cstr_transformer = ('expression, 'a) Ast_cocci.cstr_transformer = {
  1. cstr_constant : (constant_constraint -> 'a) option;
  2. cstr_operator : (operator_constraint -> 'a) option;
  3. cstr_meta_name : (meta_name -> 'a) option;
  4. cstr_regexp : (string -> Regexp.regexp -> 'a) option;
  5. cstr_script : ((bool * script_constraint) -> 'a) option;
  6. cstr_expr : ('expression -> 'a) option;
  7. cstr_sub : (meta_name list -> 'a) option;
  8. cstr_type : (fullType -> 'a) option;
}
val empty_cstr_transformer : ('expression, 'a) cstr_transformer
val cstr_fold_sign : ('expression, 'a -> 'a) cstr_transformer -> ('expression, 'a -> 'a) cstr_transformer -> 'expression generic_constraints -> 'a -> 'a
val cstr_fold : ('expression, 'a -> 'a) cstr_transformer -> 'expression generic_constraints -> 'a -> 'a
val cstr_iter : ('expression, unit) cstr_transformer -> 'expression generic_constraints -> unit
val cstr_map : ('expression, 'expression' generic_constraints) cstr_transformer -> 'expression generic_constraints -> 'expression' generic_constraints
val cstr_push_not : 'expression generic_constraints -> 'expression generic_constraints
val cstr_meta_names : 'expression generic_constraints -> meta_name list
val cstr_pos_meta_names : 'expression generic_constraints -> meta_name list
val filter_merge_variables : (script_meta_name * meta_name * metavar * mvinit) list -> (string * string) list
val prepare_merge_variables : ('a -> ('b * (script_meta_name * meta_name * metavar * mvinit) list) option) -> 'a list -> ('b * (int * string array)) list * string array
OCaml

Innovation. Community. Security.