package coccinelle
type virtual_position = Common.parse_info * int
type parse_info =
| OriginTok of Common.parse_info
| FakeTok of string * virtual_position
| ExpandedTok of Common.parse_info * virtual_position
| AbstractLineTok of Common.parse_info
type info = {
pinfo : parse_info;
cocci_tag : (Ast_cocci.mcodekind * metavars_binding list) option ref;
comments_tag : comments_around ref;
mutable annots_tag : Token_annot.annots;
danger : danger ref;
}
and il = info list
and !'a wrap = 'a * il
and !'a wrap2 = 'a * il
and !'a wrap3 = 'a * il
and fullType = typeQualifier * typeC
and typeCbis =
| NoType
| BaseType of baseType
| Pointer of fullType
| Array of constExpression option * fullType
| Decimal of constExpression * constExpression option
| FunctionType of functionType
| Enum of string option * enumType
| StructUnion of structUnion * string option * structType
| EnumName of string
| StructUnionName of structUnion * string
| TypeName of name * fullType option
| FieldType of fullType * name * constExpression option
| ParenType of fullType
| TypeOfExpr of expression
| TypeOfType of fullType
| AutoType
and structType = field list
and field =
| DeclarationField of field_declaration
| EmptyField of info
| MacroDeclField of (string * argument wrap2 list) wrap
| CppDirectiveStruct of cpp_directive
| IfdefStruct of ifdef_directive
and enumType = oneEnumType wrap2 list
and oneEnumType = name * (info * constExpression) option
and functionType = fullType * (parameterType wrap2 list * bool wrap)
and typeQualifier = typeQualifierbis wrap
and attribute = attributebis wrap
and attr_arg = attr_arg_bis wrap
and expression = (expressionbis * exp_info ref) wrap3
and expressionbis =
| Ident of name
| Constant of constant
| StringConstant of string_fragment list * string * isWchar
| FunCall of expression * argument wrap2 list
| CondExpr of expression * expression option * expression
| Sequence of expression * expression
| Assignment of expression * assignOp * expression
| Postfix of expression * fixOp
| Infix of expression * fixOp
| Unary of expression * unaryOp
| Binary of expression * binaryOp * expression
| ArrayAccess of expression * expression
| RecordAccess of expression * name
| RecordPtAccess of expression * name
| SizeOfExpr of expression
| SizeOfType of fullType
| Cast of fullType * attribute list * expression
| StatementExpr of compound wrap
| Constructor of fullType * initialiser
| ParenExpr of expression
| New of argument wrap2 list option * argument
| Delete of bool * expression
| Defined of name
and argument = (expression, weird_argument) Common.either
and assignOp = assignOpbis wrap
and binaryOp = binaryOpbis wrap
and constExpression = expression
and string_fragment = string_fragment_bis wrap
and string_format = string_format_bis wrap
and statement = statementbis wrap3
and statementbis =
| Labeled of labeled
| Compound of compound
| ExprStatement of exprStatement
| Selection of selection
| Iteration of iteration
| Jump of jump
| Decl of declaration
| Asm of asmbody
| NestedFunc of definition
| MacroStmt
| Exec of exec_code list
| IfdefStmt1 of ifdef_directive list * statement list
and labeled =
| Label of name * statement
| Case of expression * statement
| CaseRange of expression * expression * statement
| Default of statement
and compound = statement_sequencable list
and statement_sequencable =
| StmtElem of statement
| CppDirectiveStmt of cpp_directive
| IfdefStmt of ifdef_directive
| IfdefStmt2 of ifdef_directive list * statement_sequencable list list
and exprStatement = expression option
and selection =
| If of expression * statement * statement
| Switch of expression * statement
| Ifdef_Ite of expression * statement * statement
| Ifdef_Ite2 of expression * statement * statement * statement
and iteration =
| While of expression * statement
| DoWhile of statement * expression
| For of declOrExpr * exprStatement wrap * exprStatement wrap * statement
| MacroIteration of string * argument wrap2 list * statement
and jump =
| Goto of name
| Continue
| Break
| Return
| ReturnExpr of expression
| GotoComputed of expression
and colon_option = colon_option_bis wrap
and exec_code = exec_code_bis wrap
and declaration =
| DeclList of onedecl wrap2 list wrap
| MacroDecl of (storagebis * string * argument wrap2 list * attribute list * bool) wrap
| MacroDeclInit of (storagebis * string * argument wrap2 list * initialiser) wrap
and storage = storagebis * bool
and initialiser = initialiserbis wrap
and initialiserbis =
| InitExpr of expression
| InitList of initialiser wrap2 list
| InitDesignators of designator list * initialiser
| InitFieldOld of string * initialiser
| InitIndexOld of expression * initialiser
and designator = designatorbis wrap
and designatorbis =
| DesignatorField of string
| DesignatorIndex of expression
| DesignatorRange of expression * expression
and definition = definitionbis wrap
and definitionbis = {
f_name : name;
f_type : functionType;
f_storage : storage;
f_body : compound;
f_attr : attribute list;
f_endattr : attribute list;
f_old_c_style : declaration list option;
}
and define = string wrap * (define_kind * define_val)
and define_val =
| DefineExpr of expression
| DefineStmt of statement
| DefineType of fullType
| DefineDoWhileZero of (statement * expression) wrap
| DefineFunction of definition
| DefineInit of initialiser
| DefineMulti of statement list
| DefineText of string wrap
| DefineEmpty
| DefineTodo
and includ = {
i_include : inc_file wrap;
i_rel_pos : include_rel_pos option ref;
i_overall_rel_pos : include_rel_pos option ref;
i_is_in_ifdef : bool;
i_content : (Common.filename * program) option;
}
and ifdef_guard =
| Gifdef of macro_symbol
| Gifndef of macro_symbol
| Gif_str of Lexing.position * string
| Gif of expression
| Gnone
and toplevel =
| Declaration of declaration
| Definition of definition
| CppTop of cpp_directive
| IfdefTop of ifdef_directive
| MacroTop of string * argument wrap2 list * il
| EmptyDef of il
| NotParsedCorrectly of il
| FinalDef of info
| Namespace of toplevel list * il
and program = toplevel list
and metavars_binding = (Ast_cocci.meta_name, metavar_binding_kind) Common.assoc
and metavar_binding_kind =
| MetaIdVal of string
| MetaFuncVal of string
| MetaLocalFuncVal of string
| MetaExprVal of expression * Ast_cocci.meta_name list * stripped
| MetaExprListVal of argument wrap2 list
| MetaParamVal of parameterType
| MetaParamListVal of parameterType wrap2 list
| MetaTypeVal of fullType
| MetaInitVal of initialiser
| MetaInitListVal of initialiser wrap2 list
| MetaDeclVal of declaration * declaration
| MetaFieldVal of field
| MetaFieldListVal of field list
| MetaStmtVal of statement * statement * stripped
| MetaStmtListVal of statement_sequencable list * stripped
| MetaDParamListVal of string wrap wrap2 list
| MetaFmtVal of string_format
| MetaAttrArgVal of attr_arg
| MetaFragListVal of string_fragment list
| MetaAssignOpVal of assignOp
| MetaBinaryOpVal of binaryOp
| MetaPosVal of Ast_cocci.fixpos * Ast_cocci.fixpos
| MetaPosValList of (Common.filename * string * (posl * posl) option * posl * posl) list
| MetaComValList of (Token_c.comment_like_token list * Token_c.comment_like_token list * Token_c.comment_like_token list) list
| MetaListlenVal of int
| MetaNoVal
and comments_around = {
mbefore : Token_c.comment_like_token list;
mafter : Token_c.comment_like_token list;
mbefore2 : comment_and_relative_pos list;
mafter2 : comment_and_relative_pos list;
}
and comment = Common.parse_info
val nullQualif : typeQualifierbis * 'a list
val nQ : typeQualifierbis * 'a list
val defaultInt : typeCbis
val noInstr : statementbis * 'a list
val emptyMetavarsBinding : metavars_binding
val emptyAnnotCocci : Ast_cocci.mcodekind * metavars_binding list
val emptyAnnot : (Ast_cocci.mcodekind * metavars_binding list) option
val mcode_and_env_of_cocciref :
(Ast_cocci.mcodekind * metavars_binding list) option ref ->
Ast_cocci.mcodekind * metavars_binding list
val emptyComments : comments_around
val noRelPos : unit -> include_rel_pos option ref
val noInIfdef : unit -> bool ref
val no_virt_pos : Common.parse_info * int
val fakeInfo : 'a -> info
val noi_content : (Common.filename * program) option
val mk_ty : 'a -> 'b -> (typeQualifierbis * 'c list) * ('a * 'b)
val get_type_expr : (('a * 'b ref) * 'c) -> 'b
val set_type_expr : (('a * 'b ref) * 'c) -> 'b -> unit
val get_onlytype_expr : (('a * (('b * 'c) option * 'd) ref) * 'e) -> 'b option
val get_onlylocal_expr : (('a * (('b * 'c) option * 'd) ref) * 'e) -> 'c option
val rewrap_pinfo : parse_info -> info -> info
val get_pi : parse_info -> Common.parse_info
val get_opi : parse_info -> Common.parse_info
val str_of_info : info -> string
val get_info : (Common.parse_info -> 'a) -> info -> 'a
val get_orig_info : (Common.parse_info -> 'a) -> info -> 'a
val pos_of_info : info -> int
val opos_of_info : info -> int
val line_of_info : info -> int
val col_of_info : info -> int
val file_of_info : info -> Common.filename
val mcode_of_info : info -> Ast_cocci.mcodekind
val pinfo_of_info : info -> parse_info
val parse_info_of_info : info -> Common.parse_info
val strloc_of_info : info -> string
val is_fake : info -> bool
val is_origintok : info -> bool
val info_to_fixpos : info -> Ast_cocci.fixpos
val is_test : expression -> bool
val al_comments : bool -> comments_around -> comments_around
val split_comma : 'a wrap2 list -> ('a, il) Common.either list
val unsplit_comma : ('a, il) Common.either list -> 'a wrap2 list
val split_nocomma : 'a list -> ('a, il) Common.either list
val unsplit_nocomma : ('a, il) Common.either list -> 'a list
val s_of_inc_file : inc_file -> string
val s_of_inc_file_bis : inc_file -> string
val s_of_attr : (attributebis * info list) list -> string
val str_of_name : name -> string
val get_local_ii_of_expr_inlining_ii_of_name :
((expressionbis * 'a) * il) ->
il
val info_of_type : ('a * (typeCbis * il)) -> parse_info option
val get_local_ii_of_st_inlining_ii_of_name :
(statementbis * info list) ->
info list
val name_of_parameter : parameterType -> string option
val put_annot_info :
info ->
Token_annot.annot_key ->
Token_annot.annot_val ->
unit
val get_annot_info :
info ->
Token_annot.annot_key ->
Token_annot.annot_val option
val get_comments_before : info -> Token_c.comment_like_token list
val get_comments_after : info -> Token_c.comment_like_token list
val string_of_toplevel : toplevel -> string
val string_of_inc_file : inc_file -> string
sectionYPositions = computeSectionYPositions($el), 10)"
x-init="setTimeout(() => sectionYPositions = computeSectionYPositions($el), 10)"
>