package coccinelle
val default_token_info : token_info
type mcodekind = Ast0_cocci.mcodekind =
| MINUS of (Ast_cocci.anything Ast_cocci.replacement * token_info) ref
| PLUS of Ast_cocci.count
| CONTEXT of (Ast_cocci.anything Ast_cocci.befaft * token_info * token_info) ref
| MIXED of (Ast_cocci.anything Ast_cocci.befaft * token_info * token_info) ref
type info = Ast0_cocci.info = {
pos_info : position_info;
whitespace : string;
attachable_start : bool;
attachable_end : bool;
mcode_start : mcodekind list;
mcode_end : mcodekind list;
strings_before : (Ast_cocci.added_string * position_info) list;
strings_after : (Ast_cocci.added_string * position_info) list;
isSymbolIdent : bool;
}
and !'a wrap = 'a Ast0_cocci.wrap = {
node : 'a;
info : info;
index : int ref;
mcodekind : mcodekind ref;
exp_ty : typeC option ref;
bef_aft : dots_bef_aft;
true_if_arg : bool;
true_if_test : bool;
true_if_test_exp : bool;
iso_info : (string * anything) list;
}
and dots_bef_aft = Ast0_cocci.dots_bef_aft =
and !'a dots = 'a list wrap
and base_ident = Ast0_cocci.base_ident =
| Id of string mcode
| MetaId of Ast_cocci.meta_name mcode * constraints * Ast_cocci.seed * pure
| MetaFunc of Ast_cocci.meta_name mcode * constraints * pure
| MetaLocalFunc of Ast_cocci.meta_name mcode * constraints * pure
| AsIdent of ident * ident
| DisjId of string mcode * ident list * string mcode list * string mcode
| ConjId of string mcode * ident list * string mcode list * string mcode
| OptIdent of ident
and ident = base_ident wrap
and base_expression = Ast0_cocci.base_expression =
| Ident of ident
| Constant of Ast_cocci.constant mcode
| StringConstant of string mcode * string_fragment dots * string mcode * Ast_cocci.isWchar
| FunCall of expression * string mcode * expression dots * string mcode
| Assignment of expression * assignOp * expression * bool
| Sequence of expression * string mcode * expression
| CondExpr of expression * string mcode * expression option * string mcode * expression
| Postfix of expression * Ast_cocci.fixOp mcode
| Infix of expression * Ast_cocci.fixOp mcode
| Unary of expression * Ast_cocci.unaryOp mcode
| Binary of expression * binaryOp * expression
| Nested of expression * binaryOp * expression
| Paren of string mcode * expression * string mcode
| ArrayAccess of expression * string mcode * expression * string mcode
| RecordAccess of expression * string mcode * ident
| RecordPtAccess of expression * string mcode * ident
| Cast of string mcode * typeC * attr list * string mcode * expression
| SizeOfExpr of string mcode * expression
| SizeOfType of string mcode * string mcode * typeC * string mcode
| TypeExp of typeC
| Constructor of string mcode * typeC * string mcode * initialiser
| MetaErr of Ast_cocci.meta_name mcode * constraints * pure
| MetaExpr of Ast_cocci.meta_name mcode * constraints * typeC list option * Ast_cocci.form * pure * listlen option
| MetaExprList of Ast_cocci.meta_name mcode * listlen * constraints * pure
| AsExpr of expression * expression
| AsSExpr of expression * statement
| EComma of string mcode
| DisjExpr of string mcode * expression list * string mcode list * string mcode
| ConjExpr of string mcode * expression list * string mcode list * string mcode
| NestExpr of string mcode * expression dots * string mcode * (string mcode * string mcode * expression) option * Ast_cocci.multi
| Edots of string mcode * (string mcode * string mcode * expression) option
| OptExp of expression
and expression = base_expression wrap
and constraints = expression Ast_cocci.generic_constraints
and listlen = Ast0_cocci.listlen =
| MetaListLen of Ast_cocci.meta_name mcode * constraints
| CstListLen of int
| AnyListLen
and base_string_fragment = Ast0_cocci.base_string_fragment =
| ConstantFragment of string mcode
| FormatFragment of string mcode * string_format
| Strdots of string mcode
| MetaFormatList of string mcode * Ast_cocci.meta_name mcode * constraints * listlen
and string_fragment = base_string_fragment wrap
and base_string_format = Ast0_cocci.base_string_format =
| ConstantFormat of string mcode
| MetaFormat of Ast_cocci.meta_name mcode * constraints
and string_format = base_string_format wrap
and base_assignOp = Ast0_cocci.base_assignOp =
| SimpleAssign of simpleAssignOp mcode
| OpAssign of Ast_cocci.arithOp mcode
| MetaAssign of Ast_cocci.meta_name mcode * constraints * pure
and assignOp = base_assignOp wrap
and base_binaryOp = Ast0_cocci.base_binaryOp =
| Arith of Ast_cocci.arithOp mcode
| Logical of Ast_cocci.logicalOp mcode
| MetaBinary of Ast_cocci.meta_name mcode * constraints * pure
and binaryOp = base_binaryOp wrap
and base_typeC = Ast0_cocci.base_typeC =
| ConstVol of Ast_cocci.const_vol mcode list * typeC
| BaseType of Ast_cocci.baseType * string mcode list
| Signed of Ast_cocci.sign mcode * typeC option
| Pointer of typeC * string mcode
| ParenType of string mcode * typeC * string mcode
| FunctionType of typeC * string mcode * parameter_list * string mcode
| Array of typeC * string mcode * expression option * string mcode
| Decimal of string mcode * string mcode * expression * string mcode option * expression option * string mcode
| EnumName of string mcode * ident option
| EnumDef of typeC * string mcode * enum_decl dots * string mcode
| StructUnionName of Ast_cocci.structUnion mcode * ident option
| StructUnionDef of typeC * string mcode * field dots * string mcode
| TypeOfExpr of string mcode * string mcode * expression * string mcode
| TypeOfType of string mcode * string mcode * typeC * string mcode
| TypeName of string mcode
| AutoType of string mcode
| MetaType of Ast_cocci.meta_name mcode * constraints * pure
| AsType of typeC * typeC
| DisjType of string mcode * typeC list * string mcode list * string mcode
| ConjType of string mcode * typeC list * string mcode list * string mcode
| OptType of typeC
and typeC = base_typeC wrap
and base_declaration = Ast0_cocci.base_declaration =
| MetaDecl of Ast_cocci.meta_name mcode * constraints * pure
| AsDecl of declaration * declaration
| Init of Ast_cocci.storage mcode option * typeC * attr list * ident * attr list * string mcode * initialiser * string mcode
| UnInit of Ast_cocci.storage mcode option * typeC * attr list * ident * attr list * string mcode
| FunProto of fninfo list * attr list * ident * string mcode * parameter_list * (string mcode * string mcode) option * string mcode * string mcode
| TyDecl of typeC * attr list * string mcode
| MacroDecl of Ast_cocci.storage mcode option * ident * string mcode * expression dots * string mcode * attr list * string mcode
| MacroDeclInit of Ast_cocci.storage mcode option * ident * string mcode * expression dots * string mcode * string mcode * initialiser * string mcode
| Typedef of string mcode * typeC * typeC * string mcode
| DisjDecl of string mcode * declaration list * string mcode list * string mcode
| ConjDecl of string mcode * declaration list * string mcode list * string mcode
| OptDecl of declaration
and declaration = base_declaration wrap
and base_field = Ast0_cocci.base_field =
| MetaField of Ast_cocci.meta_name mcode * constraints * pure
| MetaFieldList of Ast_cocci.meta_name mcode * listlen * constraints * pure
| Field of typeC * ident option * bitfield option * string mcode
| DisjField of string mcode * field list * string mcode list * string mcode
| ConjField of string mcode * field list * string mcode list * string mcode
| Fdots of string mcode * (string mcode * string mcode * field) option
| OptField of field
and bitfield = string mcode * expression
and field = base_field wrap
and base_enum_decl = Ast0_cocci.base_enum_decl =
and enum_decl = base_enum_decl wrap
and base_initialiser = Ast0_cocci.base_initialiser =
| MetaInit of Ast_cocci.meta_name mcode * constraints * pure
| MetaInitList of Ast_cocci.meta_name mcode * listlen * constraints * pure
| AsInit of initialiser * initialiser
| InitExpr of expression
| InitList of string mcode * initialiser_list * string mcode * bool
| InitGccExt of designator list * string mcode * initialiser
| InitGccName of ident * string mcode * initialiser
| IComma of string mcode
| Idots of string mcode * (string mcode * string mcode * initialiser) option
| OptIni of initialiser
and designator = Ast0_cocci.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
and base_parameterTypeDef = Ast0_cocci.base_parameterTypeDef =
| VoidParam of typeC * attr list
| Param of typeC * attr list * ident option * attr list
| MetaParam of Ast_cocci.meta_name mcode * constraints * pure
| MetaParamList of Ast_cocci.meta_name mcode * listlen * constraints * pure
| AsParam of parameterTypeDef * expression
| PComma of string mcode
| Pdots of string mcode
| OptParam of parameterTypeDef
and parameterTypeDef = base_parameterTypeDef wrap
and parameter_list = parameterTypeDef dots
and base_define_param = Ast0_cocci.base_define_param =
| DParam of ident
| MetaDParamList of Ast_cocci.meta_name mcode * listlen * constraints * pure
| DPComma of string mcode
| DPdots of string mcode
| OptDParam of define_param
and define_param = base_define_param wrap
and base_define_parameters = Ast0_cocci.base_define_parameters =
| NoParams
| DParams of string mcode * define_param dots * string mcode
and define_parameters = base_define_parameters wrap
and base_statement = Ast0_cocci.base_statement =
| Decl of info * mcodekind * declaration
| Seq of string mcode * statement dots * string mcode
| ExprStatement of expression option * string mcode
| IfThen of string mcode * string mcode * expression * string mcode * statement * fake_mcode
| IfThenElse of string mcode * string mcode * expression * string mcode * statement * string mcode * statement * fake_mcode
| While of string mcode * string mcode * expression * string mcode * statement * fake_mcode
| Do of string mcode * statement * string mcode * string mcode * expression * string mcode * string mcode
| For of string mcode * string mcode * forinfo * expression option * string mcode * expression option * string mcode * statement * fake_mcode
| Iterator of ident * string mcode * expression dots * string mcode * statement * fake_mcode
| Switch of string mcode * string mcode * expression * string mcode * string mcode * statement dots * case_line dots * string mcode
| Break of string mcode * string mcode
| Continue of string mcode * string mcode
| Label of ident * string mcode
| Goto of string mcode * ident * string mcode
| Return of string mcode * string mcode
| ReturnExpr of string mcode * expression * string mcode
| Exec of string mcode * string mcode * exec_code dots * string mcode
| MetaStmt of Ast_cocci.meta_name mcode * constraints * pure
| MetaStmtList of Ast_cocci.meta_name mcode * listlen * constraints * pure
| AsStmt of statement * statement
| Exp of expression
| TopExp of expression
| Ty of typeC
| TopId of ident
| TopInit of initialiser
| Disj of string mcode * statement dots list * string mcode list * string mcode
| Conj of string mcode * statement dots list * string mcode list * string mcode
| Nest of string mcode * statement dots * string mcode * (statement dots, statement) whencode list * Ast_cocci.multi
| Dots of string mcode * (statement dots, statement) whencode list
| FunDecl of info * mcodekind * fninfo list * ident * string mcode * parameter_list * (string mcode * string mcode) option * string mcode * attr list * string mcode * statement dots * string mcode * info * mcodekind
| Include of string mcode * Ast_cocci.inc_file mcode
| MetaInclude of string mcode * expression
| Undef of string mcode * ident
| Define of string mcode * ident * define_parameters * statement dots
| Pragma of string mcode * ident * pragmainfo
| OptStm of statement
and base_pragmainfo = Ast0_cocci.base_pragmainfo =
and pragmainfo = base_pragmainfo wrap
and base_forinfo = Ast0_cocci.base_forinfo =
| ForExp of expression option * string mcode
| ForDecl of info * mcodekind * declaration
and forinfo = base_forinfo wrap
and fninfo = Ast0_cocci.fninfo =
| FStorage of Ast_cocci.storage mcode
| FType of typeC
| FInline of string mcode
| FAttr of attr
and base_attr = Ast0_cocci.base_attr =
| Attribute of Ast0_cocci.attr_arg
| GccAttribute of string mcode * string mcode * string mcode * Ast0_cocci.attr_arg * string mcode * string mcode
and base_attr_arg = Ast0_cocci.base_attr_arg =
| MacroAttr of string mcode
| MacroAttrArgs of string mcode * string mcode * expression dots * string mcode
| MetaAttr of Ast_cocci.meta_name mcode * constraints * pure
and attr_arg = base_attr_arg wrap
and (!'a, !'b) whencode = ('a, 'b) Ast0_cocci.whencode =
| WhenNot of string mcode * string mcode * 'a
| WhenAlways of string mcode * string mcode * 'b
| WhenModifier of string mcode * Ast_cocci.when_modifier
| WhenNotTrue of string mcode * string mcode * expression
| WhenNotFalse of string mcode * string mcode * expression
and statement = base_statement wrap
and case_line = base_case_line wrap
and base_exec_code = Ast0_cocci.base_exec_code =
| ExecEval of string mcode * expression
| ExecToken of string mcode
| ExecDots of string mcode
and exec_code = base_exec_code wrap
and meta_pos = Ast0_cocci.meta_pos =
| MetaPos of Ast_cocci.meta_name mcode * constraints * Ast_cocci.meta_collect
| MetaCom of Ast_cocci.meta_name mcode * constraints
and base_top_level = Ast0_cocci.base_top_level =
and top_level = base_top_level wrap
and rule = top_level list
and parsed_rule = Ast0_cocci.parsed_rule =
| CocciRule of rule * Ast_cocci.metavar list * (string list * string list * Ast_cocci.dependency * string * Ast_cocci.exists) * rule * Ast_cocci.metavar list * Ast_cocci.metavar list * Ast_cocci.ruletype
| ScriptRule of string * string * Ast_cocci.dependency * (Ast_cocci.script_meta_name * Ast_cocci.meta_name * Ast_cocci.metavar * Ast_cocci.mvinit) list * Ast_cocci.meta_name list * Ast_cocci.script_position * string
| InitialScriptRule of string * string * Ast_cocci.dependency * (Ast_cocci.script_meta_name * Ast_cocci.meta_name * Ast_cocci.metavar * Ast_cocci.mvinit) list * Ast_cocci.script_position * string
| FinalScriptRule of string * string * Ast_cocci.dependency * (Ast_cocci.script_meta_name * Ast_cocci.meta_name * Ast_cocci.metavar * Ast_cocci.mvinit) list * Ast_cocci.script_position * string
and anything = Ast0_cocci.anything =
| DotsExprTag of expression dots
| DotsInitTag of initialiser dots
| DotsParamTag of parameterTypeDef dots
| DotsStmtTag of statement dots
| DotsDeclTag of declaration dots
| DotsFieldTag of field dots
| DotsEnumDeclTag of enum_decl dots
| DotsCaseTag of case_line dots
| DotsDefParamTag of define_param dots
| IdentTag of ident
| ExprTag of expression
| AssignOpTag of assignOp
| BinaryOpTag of binaryOp
| ArgExprTag of expression
| TestExprTag of expression
| TypeCTag of typeC
| ParamTag of parameterTypeDef
| InitTag of initialiser
| DeclTag of declaration
| FieldTag of field
| EnumDeclTag of enum_decl
| StmtTag of statement
| ForInfoTag of forinfo
| CaseLineTag of case_line
| StringFragmentTag of string_fragment
| AttributeTag of attr
| AttrArgTag of attr_arg
| TopTag of top_level
| IsoWhenTag of Ast_cocci.when_modifier
| IsoWhenTTag of expression
| IsoWhenFTag of expression
| MetaPosTag of meta_pos
| HiddenVarTag of anything list
| WhenTag of string mcode * string mcode option * anything
val dotsExpr : expression dots -> anything
val dotsInit : initialiser dots -> anything
val dotsParam : parameterTypeDef dots -> anything
val dotsDecl : declaration dots -> anything
val dotsDefParam : define_param dots -> anything
val expr : expression -> anything
val param : parameterTypeDef -> anything
val ini : initialiser -> anything
val decl : declaration -> anything
val string_fragment : string_fragment -> anything
val default_info : unit -> info
val default_befaft : unit -> mcodekind
val context_befaft : unit -> mcodekind
val wrap : 'a -> 'a wrap
val context_wrap : 'a -> 'a wrap
val unwrap : 'a wrap -> 'a
val unwrap_mcode : 'a mcode -> 'a
val get_index : 'a wrap -> int
val set_index : 'a wrap -> int -> unit
val get_line : 'a wrap -> int
val get_mcode_line : 'a mcode -> int
val get_mcode_logline : 'a mcode -> int
val get_line_end : 'a wrap -> int
val set_dots_bef_aft : statement -> dots_bef_aft -> statement
val get_dots_bef_aft : 'a wrap -> dots_bef_aft
val set_arg_exp : expression -> expression
val get_arg_exp : expression -> bool
val set_test_pos : expression -> expression
val get_test_pos : 'a wrap -> bool
val set_test_exp : expression -> expression
val clear_test_exp : expression -> expression
val get_test_exp : 'a wrap -> bool
val make_mcode : 'a -> 'a mcode
val make_minus_mcode : 'a -> 'a mcode
val get_rule_name : parsed_rule -> string
val meta_pos_name : anything -> Ast_cocci.meta_name mcode
val meta_names_of_typeC : typeC -> Ast_cocci.meta_name list
val meta_pos_constraint_names : anything -> Ast_cocci.meta_name list
val rule_name : string ref
val string_of_assignOp : assignOp -> string
val string_of_binaryOp : binaryOp -> string
val is_unknown_type : typeC -> bool
sectionYPositions = computeSectionYPositions($el), 10)"
x-init="setTimeout(() => sectionYPositions = computeSectionYPositions($el), 10)"
>