sig
  val initCIL : unit -> unit
  val cilVersion : string
  val cilVersionMajor : int
  val cilVersionMinor : int
  val cilVersionRevision : int
  type file = {
    mutable fileName : string;
    mutable globals : Cil.global list;
    mutable globinit : Cil.fundec option;
    mutable globinitcalled : bool;
  }
  and comment = Cil.location * string
  and global =
      GType of Cil.typeinfo * Cil.location
    | GCompTag of Cil.compinfo * Cil.location
    | GCompTagDecl of Cil.compinfo * Cil.location
    | GEnumTag of Cil.enuminfo * Cil.location
    | GEnumTagDecl of Cil.enuminfo * Cil.location
    | GVarDecl of Cil.varinfo * Cil.location
    | GVar of Cil.varinfo * Cil.initinfo * Cil.location
    | GFun of Cil.fundec * Cil.location
    | GAsm of string * Cil.location
    | GPragma of Cil.attribute * Cil.location
    | GText of string
  and typ =
      TVoid of Cil.attributes
    | TInt of Cil.ikind * Cil.attributes
    | TFloat of Cil.fkind * Cil.attributes
    | TPtr of Cil.typ * Cil.attributes
    | TArray of Cil.typ * Cil.exp option * Cil.attributes
    | TFun of Cil.typ * (string * Cil.typ * Cil.attributes) list option *
        bool * Cil.attributes
    | TNamed of Cil.typeinfo * Cil.attributes
    | TComp of Cil.compinfo * Cil.attributes
    | TEnum of Cil.enuminfo * Cil.attributes
    | TBuiltin_va_list of Cil.attributes
  and ikind =
      IChar
    | ISChar
    | IUChar
    | IBool
    | IInt
    | IUInt
    | IShort
    | IUShort
    | ILong
    | IULong
    | ILongLong
    | IULongLong
  and fkind = FFloat | FDouble | FLongDouble
  and attribute = Attr of string * Cil.attrparam list
  and attributes = Cil.attribute list
  and attrparam =
      AInt of int
    | AStr of string
    | ACons of string * Cil.attrparam list
    | ASizeOf of Cil.typ
    | ASizeOfE of Cil.attrparam
    | ASizeOfS of Cil.typsig
    | AAlignOf of Cil.typ
    | AAlignOfE of Cil.attrparam
    | AAlignOfS of Cil.typsig
    | AUnOp of Cil.unop * Cil.attrparam
    | ABinOp of Cil.binop * Cil.attrparam * Cil.attrparam
    | ADot of Cil.attrparam * string
    | AStar of Cil.attrparam
    | AAddrOf of Cil.attrparam
    | AIndex of Cil.attrparam * Cil.attrparam
    | AQuestion of Cil.attrparam * Cil.attrparam * Cil.attrparam
  and compinfo = {
    mutable cstruct : bool;
    mutable cname : string;
    mutable ckey : int;
    mutable cfields : Cil.fieldinfo list;
    mutable cattr : Cil.attributes;
    mutable cdefined : bool;
    mutable creferenced : bool;
  }
  and fieldinfo = {
    mutable fcomp : Cil.compinfo;
    mutable fname : string;
    mutable ftype : Cil.typ;
    mutable fbitfield : int option;
    mutable fattr : Cil.attributes;
    mutable floc : Cil.location;
  }
  and enuminfo = {
    mutable ename : string;
    mutable eitems : (string * Cil.exp * Cil.location) list;
    mutable eattr : Cil.attributes;
    mutable ereferenced : bool;
    mutable ekind : Cil.ikind;
  }
  and typeinfo = {
    mutable tname : string;
    mutable ttype : Cil.typ;
    mutable treferenced : bool;
  }
  and varinfo = {
    mutable vname : string;
    mutable vtype : Cil.typ;
    mutable vattr : Cil.attributes;
    mutable vstorage : Cil.storage;
    mutable vglob : bool;
    mutable vinline : bool;
    mutable vdecl : Cil.location;
    mutable vid : int;
    mutable vaddrof : bool;
    mutable vreferenced : bool;
    mutable vdescr : Pretty.doc;
    mutable vdescrpure : bool;
  }
  and storage = NoStorage | Static | Register | Extern
  and exp =
      Const of Cil.constant
    | Lval of Cil.lval
    | SizeOf of Cil.typ
    | SizeOfE of Cil.exp
    | SizeOfStr of string
    | AlignOf of Cil.typ
    | AlignOfE of Cil.exp
    | UnOp of Cil.unop * Cil.exp * Cil.typ
    | BinOp of Cil.binop * Cil.exp * Cil.exp * Cil.typ
    | CastE of Cil.typ * Cil.exp
    | AddrOf of Cil.lval
    | StartOf of Cil.lval
  and constant =
      CInt64 of int64 * Cil.ikind * string option
    | CStr of string
    | CWStr of int64 list
    | CChr of char
    | CReal of float * Cil.fkind * string option
    | CEnum of Cil.exp * string * Cil.enuminfo
  and unop = Neg | BNot | LNot
  and binop =
      PlusA
    | PlusPI
    | IndexPI
    | MinusA
    | MinusPI
    | MinusPP
    | Mult
    | Div
    | Mod
    | Shiftlt
    | Shiftrt
    | Lt
    | Gt
    | Le
    | Ge
    | Eq
    | Ne
    | BAnd
    | BXor
    | BOr
    | LAnd
    | LOr
  and lval = Cil.lhost * Cil.offset
  and lhost = Var of Cil.varinfo | Mem of Cil.exp
  and offset =
      NoOffset
    | Field of Cil.fieldinfo * Cil.offset
    | Index of Cil.exp * Cil.offset
  and init =
      SingleInit of Cil.exp
    | CompoundInit of Cil.typ * (Cil.offset * Cil.init) list
  and initinfo = { mutable init : Cil.init option; }
  and fundec = {
    mutable svar : Cil.varinfo;
    mutable sformals : Cil.varinfo list;
    mutable slocals : Cil.varinfo list;
    mutable smaxid : int;
    mutable sbody : Cil.block;
    mutable smaxstmtid : int option;
    mutable sallstmts : Cil.stmt list;
  }
  and block = {
    mutable battrs : Cil.attributes;
    mutable bstmts : Cil.stmt list;
  }
  and stmt = {
    mutable labels : Cil.label list;
    mutable skind : Cil.stmtkind;
    mutable sid : int;
    mutable succs : Cil.stmt list;
    mutable preds : Cil.stmt list;
  }
  and label =
      Label of string * Cil.location * bool
    | Case of Cil.exp * Cil.location
    | Default of Cil.location
  and stmtkind =
      Instr of Cil.instr list
    | Return of Cil.exp option * Cil.location
    | Goto of Cil.stmt Pervasives.ref * Cil.location
    | Break of Cil.location
    | Continue of Cil.location
    | If of Cil.exp * Cil.block * Cil.block * Cil.location
    | Switch of Cil.exp * Cil.block * Cil.stmt list * Cil.location
    | Loop of Cil.block * Cil.location * Cil.stmt option * Cil.stmt option
    | Block of Cil.block
    | TryFinally of Cil.block * Cil.block * Cil.location
    | TryExcept of Cil.block * (Cil.instr list * Cil.exp) * Cil.block *
        Cil.location
  and instr =
      Set of Cil.lval * Cil.exp * Cil.location
    | Call of Cil.lval option * Cil.exp * Cil.exp list * Cil.location
    | Asm of Cil.attributes * string list *
        (string option * string * Cil.lval) list *
        (string option * string * Cil.exp) list * string list * Cil.location
  and location = { line : int; file : string; byte : int; }
  and typsig =
      TSArray of Cil.typsig * int64 option * Cil.attribute list
    | TSPtr of Cil.typsig * Cil.attribute list
    | TSComp of bool * string * Cil.attribute list
    | TSFun of Cil.typsig * Cil.typsig list * bool * Cil.attribute list
    | TSEnum of string * Cil.attribute list
    | TSBase of Cil.typ
  val lowerConstants : bool Pervasives.ref
  val insertImplicitCasts : bool Pervasives.ref
  type featureDescr = {
    fd_enabled : bool Pervasives.ref;
    fd_name : string;
    fd_description : string;
    fd_extraopt : (string * Arg.spec * string) list;
    fd_doit : Cil.file -> unit;
    fd_post_check : bool;
  }
  val compareLoc : Cil.location -> Cil.location -> int
  val emptyFunction : string -> Cil.fundec
  val setFormals : Cil.fundec -> Cil.varinfo list -> unit
  val setFunctionType : Cil.fundec -> Cil.typ -> unit
  val setFunctionTypeMakeFormals : Cil.fundec -> Cil.typ -> unit
  val setMaxId : Cil.fundec -> unit
  val dummyFunDec : Cil.fundec
  val dummyFile : Cil.file
  val saveBinaryFile : Cil.file -> string -> unit
  val saveBinaryFileChannel : Cil.file -> Pervasives.out_channel -> unit
  val loadBinaryFile : string -> Cil.file
  val getGlobInit : ?main_name:string -> Cil.file -> Cil.fundec
  val iterGlobals : Cil.file -> (Cil.global -> unit) -> unit
  val foldGlobals : Cil.file -> ('-> Cil.global -> 'a) -> '-> 'a
  val mapGlobals : Cil.file -> (Cil.global -> Cil.global) -> unit
  val findOrCreateFunc : Cil.file -> string -> Cil.typ -> Cil.varinfo
  val new_sid : unit -> int
  val prepareCFG : Cil.fundec -> unit
  val computeCFGInfo : Cil.fundec -> bool -> unit
  val copyFunction : Cil.fundec -> string -> Cil.fundec
  val pushGlobal :
    Cil.global ->
    types:Cil.global list Pervasives.ref ->
    variables:Cil.global list Pervasives.ref -> unit
  val invalidStmt : Cil.stmt
  val builtinFunctions : (string, Cil.typ * Cil.typ list * bool) Hashtbl.t
  val gccBuiltins : (string, Cil.typ * Cil.typ list * bool) Hashtbl.t
  val msvcBuiltins : (string, Cil.typ * Cil.typ list * bool) Hashtbl.t
  val builtinLoc : Cil.location
  val makeZeroInit : Cil.typ -> Cil.init
  val foldLeftCompound :
    implicit:bool ->
    doinit:(Cil.offset -> Cil.init -> Cil.typ -> '-> 'a) ->
    ct:Cil.typ -> initl:(Cil.offset * Cil.init) list -> acc:'-> 'a
  val voidType : Cil.typ
  val isVoidType : Cil.typ -> bool
  val isVoidPtrType : Cil.typ -> bool
  val intType : Cil.typ
  val uintType : Cil.typ
  val longType : Cil.typ
  val ulongType : Cil.typ
  val charType : Cil.typ
  val charPtrType : Cil.typ
  val wcharKind : Cil.ikind Pervasives.ref
  val wcharType : Cil.typ Pervasives.ref
  val charConstPtrType : Cil.typ
  val voidPtrType : Cil.typ
  val intPtrType : Cil.typ
  val uintPtrType : Cil.typ
  val doubleType : Cil.typ
  val upointType : Cil.typ Pervasives.ref
  val typeOfSizeOf : Cil.typ Pervasives.ref
  val kindOfSizeOf : Cil.ikind Pervasives.ref
  val isSigned : Cil.ikind -> bool
  val mkCompInfo :
    bool ->
    string ->
    (Cil.compinfo ->
     (string * Cil.typ * int option * Cil.attributes * Cil.location) list) ->
    Cil.attributes -> Cil.compinfo
  val copyCompInfo : Cil.compinfo -> string -> Cil.compinfo
  val missingFieldName : string
  val compFullName : Cil.compinfo -> string
  val isCompleteType : Cil.typ -> bool
  val unrollType : Cil.typ -> Cil.typ
  val unrollTypeDeep : Cil.typ -> Cil.typ
  val separateStorageModifiers :
    Cil.attribute list -> Cil.attribute list * Cil.attribute list
  val isIntegralType : Cil.typ -> bool
  val isArithmeticType : Cil.typ -> bool
  val isPointerType : Cil.typ -> bool
  val isFunctionType : Cil.typ -> bool
  val argsToList :
    (string * Cil.typ * Cil.attributes) list option ->
    (string * Cil.typ * Cil.attributes) list
  val isArrayType : Cil.typ -> bool
  exception LenOfArray
  val lenOfArray : Cil.exp option -> int
  val getCompField : Cil.compinfo -> string -> Cil.fieldinfo
  type existsAction = ExistsTrue | ExistsFalse | ExistsMaybe
  val existsType : (Cil.typ -> Cil.existsAction) -> Cil.typ -> bool
  val splitFunctionType :
    Cil.typ ->
    Cil.typ * (string * Cil.typ * Cil.attributes) list option * bool *
    Cil.attributes
  val splitFunctionTypeVI :
    Cil.varinfo ->
    Cil.typ * (string * Cil.typ * Cil.attributes) list option * bool *
    Cil.attributes
  val d_typsig : unit -> Cil.typsig -> Pretty.doc
  val typeSig : Cil.typ -> Cil.typsig
  val typeSigWithAttrs :
    ?ignoreSign:bool ->
    (Cil.attributes -> Cil.attributes) -> Cil.typ -> Cil.typsig
  val setTypeSigAttrs : Cil.attributes -> Cil.typsig -> Cil.typsig
  val typeSigAttrs : Cil.typsig -> Cil.attributes
  val makeVarinfo : bool -> string -> Cil.typ -> Cil.varinfo
  val makeFormalVar :
    Cil.fundec -> ?where:string -> string -> Cil.typ -> Cil.varinfo
  val makeLocalVar :
    Cil.fundec -> ?insert:bool -> string -> Cil.typ -> Cil.varinfo
  val makeTempVar :
    Cil.fundec ->
    ?insert:bool ->
    ?name:string ->
    ?descr:Pretty.doc -> ?descrpure:bool -> Cil.typ -> Cil.varinfo
  val makeGlobalVar : string -> Cil.typ -> Cil.varinfo
  val copyVarinfo : Cil.varinfo -> string -> Cil.varinfo
  val newVID : unit -> int
  val addOffsetLval : Cil.offset -> Cil.lval -> Cil.lval
  val addOffset : Cil.offset -> Cil.offset -> Cil.offset
  val removeOffsetLval : Cil.lval -> Cil.lval * Cil.offset
  val removeOffset : Cil.offset -> Cil.offset * Cil.offset
  val typeOfLval : Cil.lval -> Cil.typ
  val typeOffset : Cil.typ -> Cil.offset -> Cil.typ
  val zero : Cil.exp
  val one : Cil.exp
  val mone : Cil.exp
  val kinteger64 : Cil.ikind -> int64 -> Cil.exp
  val kinteger : Cil.ikind -> int -> Cil.exp
  val integer : int -> Cil.exp
  val isInteger : Cil.exp -> int64 option
  val i64_to_int : int64 -> int
  val isConstant : Cil.exp -> bool
  val isConstantOffset : Cil.offset -> bool
  val isZero : Cil.exp -> bool
  val charConstToInt : char -> Cil.constant
  val convertInts :
    int64 -> Cil.ikind -> int64 -> Cil.ikind -> int64 * int64 * Cil.ikind
  val constFold : bool -> Cil.exp -> Cil.exp
  val constFoldBinOp :
    bool -> Cil.binop -> Cil.exp -> Cil.exp -> Cil.typ -> Cil.exp
  val increm : Cil.exp -> int -> Cil.exp
  val var : Cil.varinfo -> Cil.lval
  val mkAddrOf : Cil.lval -> Cil.exp
  val mkAddrOrStartOf : Cil.lval -> Cil.exp
  val mkMem : addr:Cil.exp -> off:Cil.offset -> Cil.lval
  val mkString : string -> Cil.exp
  val mkCastT : e:Cil.exp -> oldt:Cil.typ -> newt:Cil.typ -> Cil.exp
  val mkCast : e:Cil.exp -> newt:Cil.typ -> Cil.exp
  val stripCasts : Cil.exp -> Cil.exp
  val typeOf : Cil.exp -> Cil.typ
  val parseInt : string -> Cil.exp
  val mkStmt : Cil.stmtkind -> Cil.stmt
  val mkBlock : Cil.stmt list -> Cil.block
  val mkStmtOneInstr : Cil.instr -> Cil.stmt
  val compactStmts : Cil.stmt list -> Cil.stmt list
  val mkEmptyStmt : unit -> Cil.stmt
  val dummyInstr : Cil.instr
  val dummyStmt : Cil.stmt
  val mkWhile : guard:Cil.exp -> body:Cil.stmt list -> Cil.stmt list
  val mkForIncr :
    iter:Cil.varinfo ->
    first:Cil.exp ->
    stopat:Cil.exp -> incr:Cil.exp -> body:Cil.stmt list -> Cil.stmt list
  val mkFor :
    start:Cil.stmt list ->
    guard:Cil.exp ->
    next:Cil.stmt list -> body:Cil.stmt list -> Cil.stmt list
  type attributeClass = AttrName of bool | AttrFunType of bool | AttrType
  val attributeHash : (string, Cil.attributeClass) Hashtbl.t
  val partitionAttributes :
    default:Cil.attributeClass ->
    Cil.attributes ->
    Cil.attribute list * Cil.attribute list * Cil.attribute list
  val addAttribute : Cil.attribute -> Cil.attributes -> Cil.attributes
  val addAttributes : Cil.attribute list -> Cil.attributes -> Cil.attributes
  val dropAttribute : string -> Cil.attributes -> Cil.attributes
  val dropAttributes : string list -> Cil.attributes -> Cil.attributes
  val filterAttributes : string -> Cil.attributes -> Cil.attributes
  val hasAttribute : string -> Cil.attributes -> bool
  val typeAttrs : Cil.typ -> Cil.attribute list
  val setTypeAttrs : Cil.typ -> Cil.attributes -> Cil.typ
  val typeAddAttributes : Cil.attribute list -> Cil.typ -> Cil.typ
  val typeRemoveAttributes : string list -> Cil.typ -> Cil.typ
  val expToAttrParam : Cil.exp -> Cil.attrparam
  exception NotAnAttrParam of Cil.exp
  type 'a visitAction =
      SkipChildren
    | DoChildren
    | ChangeTo of 'a
    | ChangeDoChildrenPost of 'a * ('-> 'a)
  class type cilVisitor =
    object
      method queueInstr : Cil.instr list -> unit
      method unqueueInstr : unit -> Cil.instr list
      method vattr : Cil.attribute -> Cil.attribute list Cil.visitAction
      method vattrparam : Cil.attrparam -> Cil.attrparam Cil.visitAction
      method vblock : Cil.block -> Cil.block Cil.visitAction
      method vexpr : Cil.exp -> Cil.exp Cil.visitAction
      method vfunc : Cil.fundec -> Cil.fundec Cil.visitAction
      method vglob : Cil.global -> Cil.global list Cil.visitAction
      method vinit :
        Cil.varinfo -> Cil.offset -> Cil.init -> Cil.init Cil.visitAction
      method vinitoffs : Cil.offset -> Cil.offset Cil.visitAction
      method vinst : Cil.instr -> Cil.instr list Cil.visitAction
      method vlval : Cil.lval -> Cil.lval Cil.visitAction
      method voffs : Cil.offset -> Cil.offset Cil.visitAction
      method vstmt : Cil.stmt -> Cil.stmt Cil.visitAction
      method vtype : Cil.typ -> Cil.typ Cil.visitAction
      method vvdec : Cil.varinfo -> Cil.varinfo Cil.visitAction
      method vvrbl : Cil.varinfo -> Cil.varinfo Cil.visitAction
    end
  class nopCilVisitor : cilVisitor
  val visitCilFile : Cil.cilVisitor -> Cil.file -> unit
  val visitCilFileSameGlobals : Cil.cilVisitor -> Cil.file -> unit
  val visitCilGlobal : Cil.cilVisitor -> Cil.global -> Cil.global list
  val visitCilFunction : Cil.cilVisitor -> Cil.fundec -> Cil.fundec
  val visitCilExpr : Cil.cilVisitor -> Cil.exp -> Cil.exp
  val visitCilLval : Cil.cilVisitor -> Cil.lval -> Cil.lval
  val visitCilOffset : Cil.cilVisitor -> Cil.offset -> Cil.offset
  val visitCilInitOffset : Cil.cilVisitor -> Cil.offset -> Cil.offset
  val visitCilInstr : Cil.cilVisitor -> Cil.instr -> Cil.instr list
  val visitCilStmt : Cil.cilVisitor -> Cil.stmt -> Cil.stmt
  val visitCilBlock : Cil.cilVisitor -> Cil.block -> Cil.block
  val visitCilType : Cil.cilVisitor -> Cil.typ -> Cil.typ
  val visitCilVarDecl : Cil.cilVisitor -> Cil.varinfo -> Cil.varinfo
  val visitCilInit :
    Cil.cilVisitor -> Cil.varinfo -> Cil.offset -> Cil.init -> Cil.init
  val visitCilAttributes :
    Cil.cilVisitor -> Cil.attribute list -> Cil.attribute list
  val msvcMode : bool Pervasives.ref
  val useLogicalOperators : bool Pervasives.ref
  val oldstyleExternInline : bool Pervasives.ref
  val constFoldVisitor : bool -> Cil.cilVisitor
  type lineDirectiveStyle =
      LineComment
    | LineCommentSparse
    | LinePreprocessorInput
    | LinePreprocessorOutput
  val lineDirectiveStyle : Cil.lineDirectiveStyle option Pervasives.ref
  val print_CIL_Input : bool Pervasives.ref
  val printCilAsIs : bool Pervasives.ref
  val lineLength : int Pervasives.ref
  val forgcc : string -> string
  val currentLoc : Cil.location Pervasives.ref
  val currentGlobal : Cil.global Pervasives.ref
  val d_loc : unit -> Cil.location -> Pretty.doc
  val d_thisloc : unit -> Pretty.doc
  val d_ikind : unit -> Cil.ikind -> Pretty.doc
  val d_fkind : unit -> Cil.fkind -> Pretty.doc
  val d_storage : unit -> Cil.storage -> Pretty.doc
  val d_const : unit -> Cil.constant -> Pretty.doc
  val derefStarLevel : int
  val indexLevel : int
  val arrowLevel : int
  val addrOfLevel : int
  val additiveLevel : int
  val comparativeLevel : int
  val bitwiseLevel : int
  val getParenthLevel : Cil.exp -> int
  class type cilPrinter =
    object
      method dBlock : Pervasives.out_channel -> int -> Cil.block -> unit
      method dGlobal : Pervasives.out_channel -> Cil.global -> unit
      method dInit : Pervasives.out_channel -> int -> Cil.init -> unit
      method dStmt : Pervasives.out_channel -> int -> Cil.stmt -> unit
      method getPrintInstrTerminator : unit -> string
      method pAttr : Cil.attribute -> Pretty.doc * bool
      method pAttrParam : unit -> Cil.attrparam -> Pretty.doc
      method pAttrs : unit -> Cil.attributes -> Pretty.doc
      method pBlock : unit -> Cil.block -> Pretty.doc
      method pExp : unit -> Cil.exp -> Pretty.doc
      method pFieldDecl : unit -> Cil.fieldinfo -> Pretty.doc
      method pGlobal : unit -> Cil.global -> Pretty.doc
      method pInit : unit -> Cil.init -> Pretty.doc
      method pInstr : unit -> Cil.instr -> Pretty.doc
      method pLabel : unit -> Cil.label -> Pretty.doc
      method pLineDirective : ?forcefile:bool -> Cil.location -> Pretty.doc
      method pLval : unit -> Cil.lval -> Pretty.doc
      method pOffset : Pretty.doc -> Cil.offset -> Pretty.doc
      method pStmt : unit -> Cil.stmt -> Pretty.doc
      method pStmtKind : Cil.stmt -> unit -> Cil.stmtkind -> Pretty.doc
      method pType : Pretty.doc option -> unit -> Cil.typ -> Pretty.doc
      method pVDecl : unit -> Cil.varinfo -> Pretty.doc
      method pVar : Cil.varinfo -> Pretty.doc
      method setCurrentFormals : Cil.varinfo list -> unit
      method setPrintInstrTerminator : string -> unit
    end
  class defaultCilPrinterClass : cilPrinter
  val defaultCilPrinter : Cil.cilPrinter
  class plainCilPrinterClass : cilPrinter
  val plainCilPrinter : Cil.cilPrinter
  class type descriptiveCilPrinter =
    object
      method dBlock : out_channel -> int -> block -> unit
      method dGlobal : out_channel -> global -> unit
      method dInit : out_channel -> int -> init -> unit
      method dStmt : out_channel -> int -> stmt -> unit
      method getPrintInstrTerminator : unit -> string
      method pAttr : attribute -> Pretty.doc * bool
      method pAttrParam : unit -> attrparam -> Pretty.doc
      method pAttrs : unit -> attributes -> Pretty.doc
      method pBlock : unit -> block -> Pretty.doc
      method pExp : unit -> exp -> Pretty.doc
      method pFieldDecl : unit -> fieldinfo -> Pretty.doc
      method pGlobal : unit -> global -> Pretty.doc
      method pInit : unit -> init -> Pretty.doc
      method pInstr : unit -> instr -> Pretty.doc
      method pLabel : unit -> label -> Pretty.doc
      method pLineDirective : ?forcefile:bool -> location -> Pretty.doc
      method pLval : unit -> lval -> Pretty.doc
      method pOffset : Pretty.doc -> offset -> Pretty.doc
      method pStmt : unit -> stmt -> Pretty.doc
      method pStmtKind : stmt -> unit -> stmtkind -> Pretty.doc
      method pTemps : unit -> Pretty.doc
      method pType : Pretty.doc option -> unit -> typ -> Pretty.doc
      method pVDecl : unit -> varinfo -> Pretty.doc
      method pVar : varinfo -> Pretty.doc
      method setCurrentFormals : varinfo list -> unit
      method setPrintInstrTerminator : string -> unit
      method startTemps : unit -> unit
      method stopTemps : unit -> unit
    end
  class descriptiveCilPrinterClass : bool -> descriptiveCilPrinter
  val descriptiveCilPrinter : Cil.descriptiveCilPrinter
  val printerForMaincil : Cil.cilPrinter Pervasives.ref
  val printType : Cil.cilPrinter -> unit -> Cil.typ -> Pretty.doc
  val printExp : Cil.cilPrinter -> unit -> Cil.exp -> Pretty.doc
  val printLval : Cil.cilPrinter -> unit -> Cil.lval -> Pretty.doc
  val printGlobal : Cil.cilPrinter -> unit -> Cil.global -> Pretty.doc
  val printAttr : Cil.cilPrinter -> unit -> Cil.attribute -> Pretty.doc
  val printAttrs : Cil.cilPrinter -> unit -> Cil.attributes -> Pretty.doc
  val printInstr : Cil.cilPrinter -> unit -> Cil.instr -> Pretty.doc
  val printStmt : Cil.cilPrinter -> unit -> Cil.stmt -> Pretty.doc
  val printBlock : Cil.cilPrinter -> unit -> Cil.block -> Pretty.doc
  val dumpStmt :
    Cil.cilPrinter -> Pervasives.out_channel -> int -> Cil.stmt -> unit
  val dumpBlock :
    Cil.cilPrinter -> Pervasives.out_channel -> int -> Cil.block -> unit
  val printInit : Cil.cilPrinter -> unit -> Cil.init -> Pretty.doc
  val dumpInit :
    Cil.cilPrinter -> Pervasives.out_channel -> int -> Cil.init -> unit
  val d_type : unit -> Cil.typ -> Pretty.doc
  val d_exp : unit -> Cil.exp -> Pretty.doc
  val d_lval : unit -> Cil.lval -> Pretty.doc
  val d_offset : Pretty.doc -> unit -> Cil.offset -> Pretty.doc
  val d_init : unit -> Cil.init -> Pretty.doc
  val d_binop : unit -> Cil.binop -> Pretty.doc
  val d_unop : unit -> Cil.unop -> Pretty.doc
  val d_attr : unit -> Cil.attribute -> Pretty.doc
  val d_attrparam : unit -> Cil.attrparam -> Pretty.doc
  val d_attrlist : unit -> Cil.attributes -> Pretty.doc
  val d_instr : unit -> Cil.instr -> Pretty.doc
  val d_label : unit -> Cil.label -> Pretty.doc
  val d_stmt : unit -> Cil.stmt -> Pretty.doc
  val d_block : unit -> Cil.block -> Pretty.doc
  val d_global : unit -> Cil.global -> Pretty.doc
  val dn_exp : unit -> Cil.exp -> Pretty.doc
  val dn_lval : unit -> Cil.lval -> Pretty.doc
  val dn_init : unit -> Cil.init -> Pretty.doc
  val dn_type : unit -> Cil.typ -> Pretty.doc
  val dn_global : unit -> Cil.global -> Pretty.doc
  val dn_attrlist : unit -> Cil.attributes -> Pretty.doc
  val dn_attr : unit -> Cil.attribute -> Pretty.doc
  val dn_attrparam : unit -> Cil.attrparam -> Pretty.doc
  val dn_stmt : unit -> Cil.stmt -> Pretty.doc
  val dn_instr : unit -> Cil.instr -> Pretty.doc
  val d_shortglobal : unit -> Cil.global -> Pretty.doc
  val dumpGlobal :
    Cil.cilPrinter -> Pervasives.out_channel -> Cil.global -> unit
  val dumpFile :
    Cil.cilPrinter -> Pervasives.out_channel -> string -> Cil.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 :
    Cil.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 :
    Cil.location -> ('a, unit, Pretty.doc) Pervasives.format -> 'a
  val d_plainexp : unit -> Cil.exp -> Pretty.doc
  val d_plaininit : unit -> Cil.init -> Pretty.doc
  val d_plainlval : unit -> Cil.lval -> Pretty.doc
  val d_plaintype : unit -> Cil.typ -> Pretty.doc
  val dd_exp : unit -> Cil.exp -> Pretty.doc
  val dd_lval : unit -> Cil.lval -> Pretty.doc
  val uniqueVarNames : Cil.file -> unit
  val peepHole2 :
    (Cil.instr * Cil.instr -> Cil.instr list option) -> Cil.stmt list -> unit
  val peepHole1 :
    (Cil.instr -> Cil.instr list option) -> Cil.stmt list -> unit
  exception SizeOfError of string * Cil.typ
  val unsignedVersionOf : Cil.ikind -> Cil.ikind
  val intKindForSize : int -> bool -> Cil.ikind
  val floatKindForSize : int -> Cil.fkind
  val bytesSizeOfInt : Cil.ikind -> int
  val bitsSizeOf : Cil.typ -> int
  val truncateInteger64 : Cil.ikind -> int64 -> int64 * bool
  val fitsInInt : Cil.ikind -> int64 -> bool
  val intKindForValue : int64 -> bool -> Cil.ikind
  val sizeOf : Cil.typ -> Cil.exp
  val alignOf_int : Cil.typ -> int
  val bitsOffset : Cil.typ -> Cil.offset -> int * int
  val char_is_unsigned : bool Pervasives.ref
  val little_endian : bool Pervasives.ref
  val underscore_name : bool Pervasives.ref
  val locUnknown : Cil.location
  val get_instrLoc : Cil.instr -> Cil.location
  val get_globalLoc : Cil.global -> Cil.location
  val get_stmtLoc : Cil.stmtkind -> Cil.location
  val dExp : Pretty.doc -> Cil.exp
  val dInstr : Pretty.doc -> Cil.location -> Cil.instr
  val dGlobal : Pretty.doc -> Cil.location -> Cil.global
  val mapNoCopy : ('-> 'a) -> 'a list -> 'a list
  val mapNoCopyList : ('-> 'a list) -> 'a list -> 'a list
  val startsWith : string -> string -> bool
  val endsWith : string -> string -> bool
  val stripUnderscores : string -> string
  type formatArg =
      Fe of Cil.exp
    | Feo of Cil.exp option
    | Fu of Cil.unop
    | Fb of Cil.binop
    | Fk of Cil.ikind
    | FE of Cil.exp list
    | Ff of (string * Cil.typ * Cil.attributes)
    | FF of (string * Cil.typ * Cil.attributes) list
    | Fva of bool
    | Fv of Cil.varinfo
    | Fl of Cil.lval
    | Flo of Cil.lval option
    | Fo of Cil.offset
    | Fc of Cil.compinfo
    | Fi of Cil.instr
    | FI of Cil.instr list
    | Ft of Cil.typ
    | Fd of int
    | Fg of string
    | Fs of Cil.stmt
    | FS of Cil.stmt list
    | FA of Cil.attributes
    | Fp of Cil.attrparam
    | FP of Cil.attrparam list
    | FX of string
  val d_formatarg : unit -> Cil.formatArg -> Pretty.doc
  val warnTruncate : bool Pervasives.ref
  val envMachine : Machdep.mach option Pervasives.ref
end