To focus the search input from anywhere on the page, press the 'S' key.
in-package search v0.1.0
Legend:
Library
Module
Module type
Parameter
Class
Class type
Library
Module
Module type
Parameter
Class
Class type
and comment = location * string
and global =
| GType of typeinfo * location
| GCompTag of compinfo * location
| GCompTagDecl of compinfo * location
| GEnumTag of enuminfo * location
| GEnumTagDecl of enuminfo * location
| GVarDecl of varinfo * location
| GVar of varinfo * initinfo * location
| GFun of fundec * location
| GAsm of string * location
| GPragma of attribute * location
| GText of string
and typ =
| TVoid of attributes
| TInt of ikind * attributes
| TFloat of fkind * attributes
| TPtr of typ * attributes
| TArray of typ * exp option * attributes
| TFun of typ * (string * typ * attributes) list option * bool * attributes
| TNamed of typeinfo * attributes
| TComp of compinfo * attributes
| TEnum of enuminfo * attributes
| TBuiltin_va_list of attributes
and attributes = attribute list
and attrparam =
| AInt of int
| AStr of string
| ACons of string * attrparam list
| ASizeOf of typ
| ASizeOfE of attrparam
| ASizeOfS of typsig
| AAlignOf of typ
| AAlignOfE of attrparam
| AAlignOfS of typsig
| AUnOp of unop * attrparam
| ABinOp of binop * attrparam * attrparam
| ADot of attrparam * string
| AStar of attrparam
| AAddrOf of attrparam
| AIndex of attrparam * attrparam
| AQuestion of attrparam * attrparam * attrparam
and compinfo = {
mutable cstruct : bool;
mutable cname : string;
mutable ckey : int;
mutable cfields : fieldinfo list;
mutable cattr : attributes;
mutable cdefined : bool;
mutable creferenced : bool;
}
and fieldinfo = {
mutable fcomp : compinfo;
mutable fname : string;
mutable ftype : typ;
mutable fbitfield : int option;
mutable fattr : attributes;
mutable floc : location;
}
and enuminfo = {
mutable ename : string;
mutable eitems : (string * exp * location) list;
mutable eattr : attributes;
mutable ereferenced : bool;
mutable ekind : ikind;
}
and varinfo = {
mutable vname : string;
mutable vtype : typ;
mutable vattr : attributes;
mutable vstorage : storage;
mutable vglob : bool;
mutable vinline : bool;
mutable vdecl : location;
vinit : initinfo;
mutable vid : int;
mutable vaddrof : bool;
mutable vreferenced : bool;
mutable vdescr : Pretty.doc;
mutable vdescrpure : bool;
}
and exp =
| Const of constant
| Lval of lval
| SizeOf of typ
| SizeOfE of exp
| SizeOfStr of string
| AlignOf of typ
| AlignOfE of exp
| UnOp of unop * exp * typ
| BinOp of binop * exp * exp * typ
| Question of exp * exp * exp * typ
| CastE of typ * exp
| AddrOf of lval
| AddrOfLabel of stmt Pervasives.ref
| StartOf of lval
and stmtkind =
| Instr of instr list
| Return of exp option * location
| Goto of stmt Pervasives.ref * location
| ComputedGoto of exp * location
| Break of location
| Continue of location
| If of exp * block * block * location
| Switch of exp * block * stmt list * location
| Loop of block * location * stmt option * stmt option
| Block of block
| TryFinally of block * block * location
| TryExcept of block * instr list * exp * block * location
val lowerConstants : bool Pervasives.ref
val insertImplicitCasts : bool Pervasives.ref
val emptyFunction : string -> fundec
val setMaxId : fundec -> unit
val dummyFunDec : fundec
val dummyFile : file
val saveBinaryFile : file -> string -> unit
val saveBinaryFileChannel : file -> Pervasives.out_channel -> unit
val loadBinaryFile : string -> file
val prepareCFG : fundec -> unit
val computeCFGInfo : fundec -> bool -> unit
val pushGlobal :
global ->
types:global list Pervasives.ref ->
variables:global list Pervasives.ref ->
unit
val invalidStmt : stmt
val builtinLoc : location
val voidType : typ
val isVoidType : typ -> bool
val isVoidPtrType : typ -> bool
val intType : typ
val uintType : typ
val longType : typ
val ulongType : typ
val charType : typ
val charPtrType : typ
val wcharKind : ikind Pervasives.ref
val wcharType : typ Pervasives.ref
val charConstPtrType : typ
val voidPtrType : typ
val intPtrType : typ
val uintPtrType : typ
val doubleType : typ
val upointType : typ Pervasives.ref
val ptrdiffType : typ Pervasives.ref
val typeOfSizeOf : typ Pervasives.ref
val kindOfSizeOf : ikind Pervasives.ref
val isSigned : ikind -> bool
val mkCompInfo :
bool ->
string ->
(compinfo -> (string * typ * int option * attributes * location) list) ->
attributes ->
compinfo
val compFullName : compinfo -> string
val isCompleteType : typ -> bool
val isIntegralType : typ -> bool
val isArithmeticType : typ -> bool
val isPointerType : typ -> bool
val isScalarType : typ -> bool
val isFunctionType : typ -> bool
val argsToList :
(string * typ * attributes) list option ->
(string * typ * attributes) list
val isArrayType : typ -> bool
val lenOfArray : exp option -> int
val existsType : (typ -> existsAction) -> typ -> bool
val splitFunctionType :
typ ->
typ * (string * typ * attributes) list option * bool * attributes
val splitFunctionTypeVI :
varinfo ->
typ * (string * typ * attributes) list option * bool * attributes
val d_typsig : unit -> typsig -> Pretty.doc
val typeSigWithAttrs :
?ignoreSign:bool ->
(attributes -> attributes) ->
typ ->
typsig
val setTypeSigAttrs : attributes -> typsig -> typsig
val typeSigAttrs : typsig -> attributes
val makeTempVar :
fundec ->
?insert:bool ->
?name:string ->
?descr:Pretty.doc ->
?descrpure:bool ->
typ ->
varinfo
val zero : exp
val one : exp
val mone : exp
val kintegerCilint : ikind -> Cilint.cilint -> exp
val integer : int -> exp
val getInteger : exp -> Cilint.cilint option
val cilint_to_int : Cilint.cilint -> int
val isConstant : exp -> bool
val isConstantOffset : offset -> bool
val isZero : exp -> bool
val charConstToInt : char -> constant
val mkString : string -> exp
val parseInt : string -> exp
val mkEmptyStmt : unit -> stmt
val dummyInstr : instr
val dummyStmt : stmt
val attributeHash : (string, attributeClass) Hashtbl.t
val partitionAttributes :
default:attributeClass ->
attributes ->
attribute list * attribute list * attribute list
val addAttribute : attribute -> attributes -> attributes
val addAttributes : attribute list -> attributes -> attributes
val dropAttribute : string -> attributes -> attributes
val dropAttributes : string list -> attributes -> attributes
val filterAttributes : string -> attributes -> attributes
val hasAttribute : string -> attributes -> bool
val setTypeAttrs : typ -> attributes -> typ
exception NotAnAttrParam of exp
class type cilVisitor = object ... end
class nopCilVisitor : cilVisitor
val visitCilFile : cilVisitor -> file -> unit
val visitCilFileSameGlobals : cilVisitor -> file -> unit
val visitCilGlobal : cilVisitor -> global -> global list
val visitCilFunction : cilVisitor -> fundec -> fundec
val visitCilExpr : cilVisitor -> exp -> exp
val visitCilLval : cilVisitor -> lval -> lval
val visitCilOffset : cilVisitor -> offset -> offset
val visitCilInitOffset : cilVisitor -> offset -> offset
val visitCilInstr : cilVisitor -> instr -> instr list
val visitCilStmt : cilVisitor -> stmt -> stmt
val visitCilBlock : cilVisitor -> block -> block
val visitCilType : cilVisitor -> typ -> typ
val visitCilVarDecl : cilVisitor -> varinfo -> varinfo
val visitCilInit : cilVisitor -> varinfo -> offset -> init -> init
val visitCilAttributes : cilVisitor -> attribute list -> attribute list
val msvcMode : bool Pervasives.ref
val makeStaticGlobal : bool Pervasives.ref
val useLogicalOperators : bool Pervasives.ref
val useComputedGoto : bool Pervasives.ref
val useCaseRange : bool Pervasives.ref
val oldstyleExternInline : bool Pervasives.ref
val constFoldVisitor : bool -> cilVisitor
val lineDirectiveStyle : lineDirectiveStyle option Pervasives.ref
val print_CIL_Input : bool Pervasives.ref
val printCilAsIs : bool Pervasives.ref
val lineLength : int Pervasives.ref
val currentLoc : location Pervasives.ref
val currentGlobal : global Pervasives.ref
val d_loc : unit -> location -> Pretty.doc
val d_thisloc : unit -> Pretty.doc
val d_ikind : unit -> ikind -> Pretty.doc
val d_fkind : unit -> fkind -> Pretty.doc
val d_storage : unit -> storage -> Pretty.doc
val d_const : unit -> constant -> Pretty.doc
val getParenthLevel : exp -> int
class type cilPrinter = object ... end
class defaultCilPrinterClass : cilPrinter
val defaultCilPrinter : cilPrinter
class plainCilPrinterClass : cilPrinter
val plainCilPrinter : cilPrinter
class type descriptiveCilPrinter = object ... end
class descriptiveCilPrinterClass : bool -> descriptiveCilPrinter
val descriptiveCilPrinter : descriptiveCilPrinter
val printerForMaincil : cilPrinter Pervasives.ref
val printType : cilPrinter -> unit -> typ -> Pretty.doc
val printExp : cilPrinter -> unit -> exp -> Pretty.doc
val printLval : cilPrinter -> unit -> lval -> Pretty.doc
val printGlobal : cilPrinter -> unit -> global -> Pretty.doc
val printAttr : cilPrinter -> unit -> attribute -> Pretty.doc
val printAttrs : cilPrinter -> unit -> attributes -> Pretty.doc
val printInstr : cilPrinter -> unit -> instr -> Pretty.doc
val printStmt : cilPrinter -> unit -> stmt -> Pretty.doc
val printBlock : cilPrinter -> unit -> block -> Pretty.doc
val dumpStmt : cilPrinter -> Pervasives.out_channel -> int -> stmt -> unit
val dumpBlock : cilPrinter -> Pervasives.out_channel -> int -> block -> unit
val printInit : cilPrinter -> unit -> init -> Pretty.doc
val dumpInit : cilPrinter -> Pervasives.out_channel -> int -> init -> unit
val d_type : unit -> typ -> Pretty.doc
val d_exp : unit -> exp -> Pretty.doc
val d_lval : unit -> lval -> Pretty.doc
val d_offset : Pretty.doc -> unit -> offset -> Pretty.doc
val d_init : unit -> init -> Pretty.doc
val d_binop : unit -> binop -> Pretty.doc
val d_unop : unit -> unop -> Pretty.doc
val d_attr : unit -> attribute -> Pretty.doc
val d_attrparam : unit -> attrparam -> Pretty.doc
val d_attrlist : unit -> attributes -> Pretty.doc
val d_instr : unit -> instr -> Pretty.doc
val d_label : unit -> label -> Pretty.doc
val d_stmt : unit -> stmt -> Pretty.doc
val d_block : unit -> block -> Pretty.doc
val d_global : unit -> global -> Pretty.doc
val dn_exp : unit -> exp -> Pretty.doc
val dn_lval : unit -> lval -> Pretty.doc
val dn_init : unit -> init -> Pretty.doc
val dn_type : unit -> typ -> Pretty.doc
val dn_global : unit -> global -> Pretty.doc
val dn_attrlist : unit -> attributes -> Pretty.doc
val dn_attr : unit -> attribute -> Pretty.doc
val dn_attrparam : unit -> attrparam -> Pretty.doc
val dn_stmt : unit -> stmt -> Pretty.doc
val dn_instr : unit -> instr -> Pretty.doc
val d_shortglobal : unit -> global -> Pretty.doc
val dumpGlobal : cilPrinter -> Pervasives.out_channel -> global -> unit
val dumpFile : cilPrinter -> Pervasives.out_channel -> string -> file -> unit
val bug : ('a, unit, Pretty.doc) Pervasives.format -> 'a
val unimp : ('a, unit, Pretty.doc) Pervasives.format -> 'a
val error : ('a, unit, Pretty.doc) Pervasives.format -> 'a
val errorLoc : location -> ('a, unit, Pretty.doc) Pervasives.format -> 'a
val warn : ('a, unit, Pretty.doc) Pervasives.format -> 'a
val warnOpt : ('a, unit, Pretty.doc) Pervasives.format -> 'a
val warnContext : ('a, unit, Pretty.doc) Pervasives.format -> 'a
val warnContextOpt : ('a, unit, Pretty.doc) Pervasives.format -> 'a
val warnLoc : location -> ('a, unit, Pretty.doc) Pervasives.format -> 'a
val d_plainexp : unit -> exp -> Pretty.doc
val d_plaininit : unit -> init -> Pretty.doc
val d_plainlval : unit -> lval -> Pretty.doc
val d_plaintype : unit -> typ -> Pretty.doc
val dd_exp : unit -> exp -> Pretty.doc
val dd_lval : unit -> lval -> Pretty.doc
val uniqueVarNames : file -> unit
exception SizeOfError of string * typ
val intRank : ikind -> int
val intKindForSize : int -> bool -> ikind
val floatKindForSize : int -> fkind
val bytesSizeOfInt : ikind -> int
val bitsSizeOf : typ -> int
val truncateCilint :
ikind ->
Cilint.cilint ->
Cilint.cilint * Cilint.truncation
val fitsInInt : ikind -> Cilint.cilint -> bool
val intKindForValue : Cilint.cilint -> bool -> ikind
val mkCilint : ikind -> int64 -> Cilint.cilint
val alignOf_int : typ -> int
val char_is_unsigned : bool Pervasives.ref
val little_endian : bool Pervasives.ref
val underscore_name : bool Pervasives.ref
val locUnknown : location
val dExp : Pretty.doc -> exp
val dInstr : Pretty.doc -> location -> instr
val dGlobal : Pretty.doc -> location -> global
type formatArg =
| Fe of exp
| Feo of exp option
| Fu of unop
| Fb of binop
| Fk of ikind
| FE of exp list
| Ff of string * typ * attributes
| FF of (string * typ * attributes) list
| Fva of bool
| Fv of varinfo
| Fl of lval
| Flo of lval option
| Fo of offset
| Fc of compinfo
| Fi of instr
| FI of instr list
| Ft of typ
| Fd of int
| Fg of string
| Fs of stmt
| FS of stmt list
| FA of attributes
| Fp of attrparam
| FP of attrparam list
| FX of string
val d_formatarg : unit -> formatArg -> Pretty.doc
val warnTruncate : bool Pervasives.ref
val envMachine : Machdep.mach option Pervasives.ref
val isInteger : exp -> int64 option
val truncateInteger64 : ikind -> int64 -> int64 * bool
sectionYPositions = computeSectionYPositions($el), 10)"
x-init="setTimeout(() => sectionYPositions = computeSectionYPositions($el), 10)"
>