package coccinelle
type info = {
line : int;
column : int;
strbef : (added_string * int * int) list;
straft : (added_string * int * int) list;
whitespace : string;
}
type script_position = string * line
type !'a wrap = {
node : 'a;
node_line : line;
free_vars : meta_name list;
minus_free_vars : meta_name list;
minus_nc_free_vars : meta_name list;
fresh_vars : (meta_name * seed) list;
inherited : meta_name list;
positive_inherited_positions : meta_name list;
constraints : (meta_name * constraints) list;
saved_witness : meta_name list;
bef_aft : dots_bef_aft;
pos_info : meta_name mcode option;
true_if_test_exp : bool;
safe_for_multi_decls : safety;
iso_info : (string * anything) list;
}
and metavar =
| MetaMetaDecl of arity * meta_name
| MetaIdDecl of arity * meta_name
| MetaFreshIdDecl of meta_name * seed
| MetaTypeDecl of arity * meta_name
| MetaInitDecl of arity * meta_name
| MetaInitListDecl of arity * meta_name * list_len
| MetaListlenDecl of meta_name
| MetaParamDecl of arity * meta_name
| MetaParamListDecl of arity * meta_name * list_len
| MetaBinaryOperatorDecl of arity * meta_name
| MetaAssignmentOperatorDecl of arity * meta_name
| MetaConstDecl of arity * meta_name * fullType list option
| MetaErrDecl of arity * meta_name
| MetaExpDecl of arity * meta_name * fullType list option * list_len option
| MetaIdExpDecl of arity * meta_name * fullType list option
| MetaLocalIdExpDecl of arity * meta_name * fullType list option
| MetaGlobalIdExpDecl of arity * meta_name * fullType list option
| MetaExpListDecl of arity * meta_name * list_len
| MetaDeclDecl of arity * meta_name
| MetaFieldDecl of arity * meta_name
| MetaFieldListDecl of arity * meta_name * list_len
| MetaStmDecl of arity * meta_name
| MetaStmListDecl of arity * meta_name * list_len
| MetaDParamListDecl of arity * meta_name * list_len
| MetaFuncDecl of arity * meta_name
| MetaLocalFuncDecl of arity * meta_name
| MetaPosDecl of arity * meta_name
| MetaComDecl of arity * meta_name
| MetaFmtDecl of arity * meta_name
| MetaAttributeDecl of arity * meta_name
| MetaFragListDecl of arity * meta_name * list_len
| MetaAnalysisDecl of string * meta_name
| MetaDeclarerDecl of arity * meta_name
| MetaIteratorDecl of arity * meta_name
| MetaScriptDecl of metavar option ref * meta_name
and seed_script =
string * string * (meta_name * metavar) list * script_position * string
and !'a dots = 'a list wrap
and base_ident =
| Id of string mcode
| MetaId of meta_name mcode * constraints * keep_binding * inherited
| MetaFunc of meta_name mcode * constraints * keep_binding * inherited
| MetaLocalFunc of meta_name mcode * constraints * keep_binding * inherited
| AsIdent of ident * ident
| DisjId of ident list
| ConjId of ident list
| OptIdent of ident
and ident = base_ident wrap
and base_expression =
| Ident of ident
| Constant of constant mcode
| StringConstant of string mcode * string_fragment dots * string mcode * 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 * fixOp mcode
| Infix of expression * fixOp mcode
| Unary of expression * unaryOp mcode
| Binary of expression * binaryOp * expression
| Nested of expression * binaryOp * expression
| ArrayAccess of expression * string mcode * expression * string mcode
| RecordAccess of expression * string mcode * ident
| RecordPtAccess of expression * string mcode * ident
| Cast of string mcode * fullType * attr list * string mcode * expression
| SizeOfExpr of string mcode * expression
| SizeOfType of string mcode * string mcode * fullType * string mcode
| TypeExp of fullType
| 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 * fullType list option * form * inherited * listlen option
| MetaExprList of meta_name mcode * listlen * constraints * keep_binding * inherited
| AsExpr of expression * expression
| AsSExpr of expression * rule_elem
| EComma of string mcode
| DisjExpr of expression list
| ConjExpr of expression list
| NestExpr of string mcode * expression dots * string mcode * expression option * multi
| Edots of string mcode * expression option
| OptExp of expression
and !'expression generic_constraints =
| CstrFalse
| CstrTrue
| CstrAnd of 'expression generic_constraints list
| CstrOr of 'expression generic_constraints list
| CstrNot of 'expression generic_constraints
| CstrConstant of constant_constraint
| CstrOperator of operator_constraint
| CstrMeta_name of meta_name
| CstrRegexp of string * Regexp.regexp
| CstrScript of bool * script_constraint
| CstrExpr of 'expression
| CstrSub of meta_name list
| CstrType of fullType
and constraints = expression generic_constraints
and script_constraint =
string * string * (meta_name * metavar) list * script_position * string
and expression = base_expression wrap
and listlen =
| MetaListLen of meta_name mcode * constraints * keep_binding * inherited
| CstListLen of int
| AnyListLen
and base_string_fragment =
| ConstantFragment of string mcode
| FormatFragment of string mcode * string_format
| Strdots of string mcode
| MetaFormatList of string mcode * meta_name mcode * listlen * constraints * keep_binding * inherited
and string_fragment = base_string_fragment wrap
and base_string_format =
| ConstantFormat of string mcode
| MetaFormat of meta_name mcode * constraints * keep_binding * inherited
and string_format = base_string_format wrap
and base_assignOp =
| SimpleAssign of simpleAssignOp mcode
| OpAssign of arithOp mcode
| MetaAssign of meta_name mcode * constraints * keep_binding * inherited
and assignOp = base_assignOp wrap
and base_binaryOp =
| Arith of arithOp mcode
| Logical of logicalOp mcode
| MetaBinary of meta_name mcode * constraints * keep_binding * inherited
and binaryOp = base_binaryOp wrap
and base_typeC =
| BaseType of baseType * string mcode list
| SignedT of sign mcode * typeC option
| Pointer of fullType * string mcode
| ParenType of string mcode * fullType * string mcode
| FunctionType of fullType * string mcode * parameter_list * string mcode
| Array of fullType * 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 fullType * string mcode * enum_decl dots * string mcode
| StructUnionName of structUnion mcode * ident option
| StructUnionDef of fullType * string mcode * annotated_field dots * string mcode
| TypeOfExpr of string mcode * string mcode * expression * string mcode
| TypeOfType of string mcode * string mcode * fullType * string mcode
| TypeName of string mcode
| AutoType of string mcode
| MetaType of meta_name mcode * constraints * keep_binding * inherited
and fullType = base_fullType wrap
and typeC = base_typeC wrap
and base_declaration =
| Init of storage mcode option * fullType * attr list * ident * attr list * string mcode * initialiser * string mcode
| UnInit of storage mcode option * fullType * 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 fullType * attr list * string mcode
| MacroDecl of storage mcode option * ident * string mcode * expression dots * string mcode * attr list * string mcode
| MacroDeclInit of storage mcode option * ident * string mcode * expression dots * string mcode * string mcode * initialiser * string mcode
| Typedef of string mcode * fullType * typeC * string mcode
| DisjDecl of declaration list
| ConjDecl of declaration list
| MetaDecl of meta_name mcode * constraints * keep_binding * inherited
| AsDecl of declaration * declaration
| OptDecl of declaration
and declaration = base_declaration wrap
and annotated_decl = base_annotated_decl wrap
and base_field =
| Field of fullType * ident option * bitfield option * string mcode
| MetaField of meta_name mcode * constraints * keep_binding * inherited
| MetaFieldList of meta_name mcode * listlen * constraints * keep_binding * inherited
and bitfield = string mcode * expression
and field = base_field wrap
and base_annotated_field =
| FElem of mcodekind * bool * field
| Fdots of string mcode * field option
| DisjField of annotated_field list
| ConjField of annotated_field list
| OptField of annotated_field
and annotated_field = base_annotated_field wrap
and enum_decl = base_enum_decl wrap
and base_initialiser =
| MetaInit of meta_name mcode * constraints * keep_binding * inherited
| MetaInitList of meta_name mcode * listlen * constraints * keep_binding * inherited
| AsInit of initialiser * initialiser
| InitExpr of expression
| ArInitList of string mcode * initialiser dots * string mcode
| StrInitList of bool * string mcode * initialiser list * string mcode * initialiser list
| InitGccExt of designator list * string mcode * initialiser
| InitGccName of ident * string mcode * initialiser
| IComma of string mcode
| Idots of string mcode * initialiser option
| OptIni 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 base_parameterTypeDef =
| VoidParam of fullType * attr list
| Param of fullType * attr list * ident option * attr list
| MetaParam of meta_name mcode * constraints * keep_binding * inherited
| MetaParamList of meta_name mcode * listlen * constraints * keep_binding * inherited
| 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 =
| DParam of ident
| MetaDParamList of meta_name mcode * listlen * constraints * keep_binding * inherited
| DPComma of string mcode
| DPdots of string mcode
| OptDParam of define_param
and define_param = base_define_param wrap
and define_parameters = base_define_parameters wrap
and meta_pos =
| MetaPos of meta_name mcode * constraints * meta_collect * keep_binding * inherited
| MetaCom of meta_name mcode * constraints * keep_binding * inherited
and base_rule_elem =
| FunHeader of mcodekind * bool * fninfo list * ident * string mcode * parameter_list * (string mcode * string mcode) option * string mcode * attr list
| Decl of annotated_decl
| SeqStart of string mcode
| SeqEnd of string mcode
| ExprStatement of expression option * string mcode
| IfHeader of string mcode * string mcode * expression * string mcode
| Else of string mcode
| WhileHeader of string mcode * string mcode * expression * string mcode
| DoHeader of string mcode
| WhileTail of string mcode * string mcode * expression * string mcode * string mcode
| ForHeader of string mcode * string mcode * forinfo * expression option * string mcode * expression option * string mcode
| IteratorHeader of ident * string mcode * expression dots * string mcode
| SwitchHeader of string mcode * string mcode * expression * 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
| MetaRuleElem of meta_name mcode * constraints * keep_binding * inherited
| MetaStmt of meta_name mcode * constraints * keep_binding * metaStmtInfo * inherited
| MetaStmtList of meta_name mcode * listlen * constraints * keep_binding * inherited
| Exp of expression
| TopExp of expression
| Ty of fullType
| TopId of ident
| TopInit of initialiser
| Include of string mcode * inc_file mcode
| MetaInclude of string mcode * expression
| Undef of string mcode * ident
| DefineHeader of string mcode * ident * define_parameters
| Pragma of string mcode * ident * pragmainfo
| Case of string mcode * expression * string mcode
| Default of string mcode * string mcode
| AsRe of rule_elem * rule_elem
| DisjRuleElem of rule_elem list
and pragmainfo = base_pragmainfo wrap
and base_attr_arg =
| MacroAttr of string mcode
| MacroAttrArgs of string mcode * string mcode * expression dots * string mcode
| MetaAttr of meta_name mcode * constraints * keep_binding * inherited
and attr_arg = base_attr_arg wrap
and rule_elem = base_rule_elem wrap
and base_statement =
| Seq of rule_elem * statement dots * rule_elem
| IfThen of rule_elem * statement * end_info
| IfThenElse of rule_elem * statement * rule_elem * statement * end_info
| While of rule_elem * statement * end_info
| Do of rule_elem * statement * rule_elem
| For of rule_elem * statement * end_info
| Iterator of rule_elem * statement * end_info
| Switch of rule_elem * rule_elem * statement dots * case_line list * rule_elem
| Atomic of rule_elem
| Disj of statement dots list
| Conj of statement dots list
| Nest of string mcode * statement dots * string mcode * (statement dots, statement) whencode list * multi * dots_whencode list * dots_whencode list
| FunDecl of rule_elem * rule_elem * statement dots * rule_elem * end_info
| Define of rule_elem * statement dots
| AsStmt of statement * statement
| Dots of string mcode * (statement dots, statement) whencode list * dots_whencode list * dots_whencode list
| OptStm of statement
and (!'a, !'b) whencode =
| WhenNot of 'a
| WhenAlways of 'b
| WhenModifier of when_modifier
| WhenNotTrue of rule_elem
| WhenNotFalse of rule_elem
and statement = base_statement wrap
and case_line = base_case_line wrap
and base_exec_code =
| ExecEval of string mcode * expression
| ExecToken of string mcode
| ExecDots of string mcode
and exec_code = base_exec_code wrap
and top_level = base_top_level wrap
and rulename =
| CocciRulename of string option * dependency * string list * string list * exists * parser_kind
| GeneratedRulename of string option * dependency * string list * string list * exists * parser_kind
| ScriptRulename of string option * string * dependency
| InitialScriptRulename of string option * string * dependency
| FinalScriptRulename of string option * string * dependency
and rule =
| CocciRule of string * dependency * string list * exists * top_level list * bool list * ruletype
| ScriptRule of string * string * dependency * (script_meta_name * meta_name * metavar * mvinit) list * meta_name list * script_position * string
| InitialScriptRule of string * string * dependency * (script_meta_name * meta_name * metavar * mvinit) list * script_position * string
| FinalScriptRule of string * string * dependency * (script_meta_name * meta_name * metavar * mvinit) list * script_position * string
and anything =
| FullTypeTag of fullType
| BaseTypeTag of baseType
| StructUnionTag of structUnion
| SignTag of sign
| IdentTag of ident
| ExpressionTag of expression
| ConstantTag of constant
| UnaryOpTag of unaryOp
| AssignOpTag of assignOp
| SimpleAssignOpTag of simpleAssignOp
| OpAssignOpTag of arithOp
| FixOpTag of fixOp
| BinaryOpTag of binaryOp
| ArithOpTag of arithOp
| LogicalOpTag of logicalOp
| DeclarationTag of declaration
| FieldTag of field
| EnumDeclTag of enum_decl
| InitTag of initialiser
| StorageTag of storage
| IncFileTag of inc_file
| Rule_elemTag of rule_elem
| StatementTag of statement
| ForInfoTag of forinfo
| CaseLineTag of case_line
| StringFragmentTag of string_fragment
| AttributeTag of attr
| AttrArgTag of attr_arg
| ConstVolTag of const_vol
| Token of string * info option
| Directive of added_string list
| Code of top_level
| ExprDotsTag of expression dots
| ParamDotsTag of parameterTypeDef dots
| StmtDotsTag of statement dots
| AnnDeclDotsTag of annotated_decl dots
| AnnFieldDotsTag of annotated_field dots
| EnumDeclDotsTag of enum_decl dots
| DefParDotsTag of define_param dots
| TypeCTag of typeC
| ParamTag of parameterTypeDef
| SgrepStartTag of string
| SgrepEndTag of string
val mkToken : string -> anything
val unwrap : 'a wrap -> 'a
val unwrap_mcode : 'a mcode -> 'a
val get_mcode_col : 'a mcode -> int
val get_constraints : 'a wrap -> (meta_name * constraints) list
val add_constraint : 'a wrap -> (meta_name * constraints) -> 'a wrap
val get_dots_bef_aft : statement -> dots_bef_aft
val set_dots_bef_aft : dots_bef_aft -> statement -> statement
val get_test_exp : 'a wrap -> bool
val set_test_exp : expression -> expression
val tag2c : anything -> string
val no_info : info
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_mcode : 'a -> 'a mcode
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 ident_of_expression_opt : expression -> ident option
val string_of_meta_name : meta_name -> string
type !'a transformer = {
baseType : (baseType -> string mcode list -> 'a) option;
decimal : (string mcode -> string mcode -> expression -> string mcode option -> expression option -> string mcode -> 'a) option;
enumName : (string mcode -> ident option -> 'a) option;
structUnionName : (structUnion mcode -> ident option -> 'a) option;
typeName : (string mcode -> 'a) option;
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 string_of_expression : expression -> string option
type (!'expression, !'a) cstr_transformer = {
cstr_constant : (constant_constraint -> 'a) option;
cstr_operator : (operator_constraint -> 'a) option;
cstr_meta_name : (meta_name -> 'a) option;
cstr_regexp : (string -> Regexp.regexp -> 'a) option;
cstr_script : ((bool * script_constraint) -> 'a) option;
cstr_expr : ('expression -> 'a) option;
cstr_sub : (meta_name list -> 'a) option;
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
sectionYPositions = computeSectionYPositions($el), 10)"
x-init="setTimeout(() => sectionYPositions = computeSectionYPositions($el), 10)"
>