module type TYPE =sig..end
type 'a typ 
typ value: the C type used to store and pass values, and the
      corresponding OCaml type.  The type parameter indicates the OCaml type, so a
      value of type t typ is used to read and write OCaml values of type t.
      There are various uses of typ values, including
Foreign.foreignCtypes_types.TYPE.ptrCtypes_types.TYPE.structure and
      Ctypes_types.TYPE.union.val void : unit typ
      Dereferencing a pointer to void is an error, as in C, and will raise
      IncompleteType.
      The scalar types consist of the Arithmetic types and the Pointer types.
      The arithmetic types consist of the signed and unsigned integer types
      (including character types) and the floating types.  There are values
      representing both exact-width integer types (of 8, 16, 32 and 64 bits) and
      types whose size depend on the platform (signed and unsigned short, int, long,
      long long).
val char : char typchar.val schar : int typsigned char.val short : int typsigned) short.val int : int typsigned) int.val long : Signed.long typsigned) long.val llong : Signed.llong typsigned) long long.val nativeint : nativeint typsigned) int.val int8_t : int typval int16_t : int typval int32_t : int32 typval int64_t : int64 typmodule Intptr:Signed.S
val intptr_t : Intptr.t typintptr_t.module Ptrdiff:Signed.S
val ptrdiff_t : Ptrdiff.t typptrdiff_t.val camlint : int typint.val uchar : Unsigned.uchar typunsigned char.val bool : bool typbool.val uint8_t : Unsigned.uint8 typval uint16_t : Unsigned.uint16 typval uint32_t : Unsigned.uint32 typval uint64_t : Unsigned.uint64 typval size_t : Unsigned.size_t typsize_t, an alias for one of the unsigned
      integer types.  The actual size and alignment requirements for size_t
      vary between platforms.val ushort : Unsigned.ushort typunsigned short.val sint : Signed.sint typint.val uint : Unsigned.uint typunsigned int.val ulong : Unsigned.ulong typunsigned long.val ullong : Unsigned.ullong typunsigned long long.module Uintptr:Unsigned.S
val uintptr_t : Uintptr.t typuintptr_t.val float : float typfloat type.val double : float typdouble.val ldouble : LDouble.t typlong double.val complex32 : Complex.t typfloat complex type.val complex64 : Complex.t typdouble complex type.val complexld : ComplexL.t typlong double complex type.val ptr : 'a typ -> 'a Ctypes_static.ptr typval ptr_opt : 'a typ -> 'a Ctypes_static.ptr option typCtypes_types.TYPE.ptr, except that null pointers appear in OCaml
      as None.val string : string typ
      On the C side this behaves like char *; on the OCaml side values read
      and written using Ctypes_types.TYPE.string are simply native OCaml strings.
      To avoid problems with the garbage collector, values passed using
      Ctypes_types.TYPE.string are copied into immovable C-managed storage before being passed
      to C.
val string_opt : string option typCtypes_types.TYPE.string,
      except that null pointers appear in OCaml as None.val ocaml_string : string Ctypes_static.ocaml typval ocaml_bytes : Bytes.t Ctypes_static.ocaml typval array : int ->
       'a typ -> 'a Ctypes_static.carray typval bigarray : < ba_repr : 'b; bigarray : 'bigarray; carray : 'c; dims : 'dims;
         element : 'a; layout : Bigarray.c_layout >
       Ctypes_static.bigarray_class ->
       'dims -> ('a, 'b) Bigarray.kind -> 'bigarray typBigarray.kind.val fortran_bigarray : < ba_repr : 'b; bigarray : 'bigarray; carray : 'c; dims : 'dims;
         element : 'a; layout : Bigarray.fortran_layout >
       Ctypes_static.bigarray_class ->
       'dims -> ('a, 'b) Bigarray.kind -> 'bigarray typBigarray.kind.val typ_of_bigarray_kind : ('a, 'b) Bigarray.kind -> 'a typtyp_of_bigarray_kind k is the type corresponding to the Bigarray kind
      k.type ('a, 't) field 
val structure : string -> 's Ctypes_static.structure typCtypes_types.TYPE.field until it is passed to Ctypes_types.TYPE.seal, at which point
      the set of fields is fixed.
      The type ('_s structure typ) of the expression returned by the call
      structure tag includes a weak type variable, which can be explicitly
      instantiated to ensure that the OCaml values representing different C
      structure types have incompatible types.  Typical usage is as follows:
      type tagname
      let tagname : tagname structure typ = structure "tagname"
val union : string -> 's Ctypes_static.union typCtypes_types.TYPE.structure;
      fields are added with Ctypes_types.TYPE.field.val field : ('s, [< `Struct | `Union ] as 'b) Ctypes_static.structured
       typ ->
       string ->
       'a typ ->
       ('a, ('s, 'b) Ctypes_static.structured) fieldfield ty label ty' adds a field of type ty' with label label to the
      structure or union type ty and returns a field value that can be used to
      read and write the field in structure or union instances (e.g. using
      getf and setf).
      Attempting to add a field to a union type that has been sealed with seal
      is an error, and will raise ModifyingSealedType.
val seal : ('a, [< `Struct | `Union ]) Ctypes_static.structured typ ->
       unitseal t completes the struct or union type t so that no further fields
      can be added.  Struct and union types must be sealed before they can be used
      in a way that involves their size or alignment; see the documentation for
      IncompleteType for further details.val view : ?format_typ:((Format.formatter -> unit) -> Format.formatter -> unit) ->
       ?format:(Format.formatter -> 'b -> unit) ->
       read:('a -> 'b) ->
       write:('b -> 'a) -> 'a typ -> 'b typview ~read:r ~write:w t creates a C type representation t' which
      behaves like t except that values read using t' are subsequently
      transformed using the function r and values written using t' are first
      transformed using the function w.
      For example, given suitable definitions of string_of_char_ptr and
      char_ptr_of_string, the type representation
      view ~read:string_of_char_ptr ~write:char_ptr_of_string (ptr char)
      can be used to pass OCaml strings directly to and from bound C functions,
      or to read and write string members in structs and arrays.  (In fact, the
      Ctypes_types.TYPE.string type representation is defined in exactly this way.)
      The optional argument format_typ is used by the Ctypes.format_typ and
      string_of_typ functions to print the type at the top level and
      elsewhere.  If format_typ is not supplied the printer for t is used
      instead.
      The optional argument format is used by the Ctypes.format
      and string_of functions to print the values. If format_val
      is not supplied the printer for t is used instead.
val typedef : 'a typ -> string -> 'a typtypedef t name creates a C type representation t' which
      is equivalent to t except its name is printed as name.
      This is useful when generating C stubs involving "anonymous" types, for
      example: typedef struct { int f } typedef_name;
val abstract : name:string ->
       size:int -> alignment:int -> 'a Ctypes_static.abstract typval lift_typ : 'a Ctypes_static.typ -> 'a typlift_typ t turns a concrete type representation into an abstract type
      representation.
      For example, retrieving struct layout from C involves working with an
      abstract representation of types which do not support operations such as
      sizeof.  The lift_typ function makes it possible to use concrete
      type representations wherever such abstract type representations are
      needed.
type'afn ='a Ctypes_static.fn
t fn
      can be used to bind to C functions and to describe type of OCaml functions
      passed to C.val (@->) : 'a typ ->
       'b fn -> ('a -> 'b) fn
      int @-> ptr void @-> returning float
      describes a function type that accepts two arguments -- an integer and a
      pointer to void -- and returns a float.
val returning : 'a typ -> 'a fnreturning is intended
      to be used together with Ctypes_types.TYPE.(@->); see the documentation for Ctypes_types.TYPE.(@->) for an
      example.type'astatic_funptr ='a Ctypes_static.static_funptr
The type of values representing C function pointer types.
val static_funptr : 'a fn ->
       'a Ctypes_static.static_funptr typ