Module Metal.Objc

include module type of Runtime.Objc
val get_class : string -> Runtime__.Type_description.Types.objc_object Ctypes.structure Ctypes_static.ptr
val get_meta_class : string -> Runtime__.Type_description.Types.objc_object Ctypes.structure Ctypes_static.ptr
val get_protocol : string -> Runtime__.Type_description.Types.objc_object Ctypes.structure Ctypes_static.ptr
val register_class : Runtime__.Type_description.Types.objc_object Ctypes.structure Ctypes_static.ptr -> unit
val get_class_list : Runtime__.Type_description.Types.objc_class Ctypes.structure Ctypes_static.ptr Ctypes_static.ptr -> int -> int
val get_protocol_list : Unsigned.uint Ctypes_static.ptr -> Runtime__.Type_description.Types.objc_object Ctypes.structure Ctypes_static.ptr Ctypes_static.ptr
val allocate_class : ?extra_bytes:Unsigned.size_t -> superclass: Runtime__.Type_description.Types.objc_object Ctypes.structure Ctypes_static.ptr -> string -> Runtime__.Type_description.Types.objc_object Ctypes.structure Ctypes_static.ptr
type objc_class = Runtime__Type_description.Types.objc_class
val objc_class : objc_class Ctypes.structure Ctypes.typ
type objc_object = Runtime__Type_description.Types.objc_object
val objc_object : objc_object Ctypes.structure Ctypes.typ
type objc_method = Runtime__Type_description.Types.objc_method
val objc_method : objc_method Ctypes.structure Ctypes.typ
type objc_selector = Runtime__Type_description.Types.objc_selector
val objc_selector : objc_selector Ctypes.structure Ctypes.typ
type objc_ivar = Runtime__Type_description.Types.objc_ivar
val objc_ivar : objc_ivar Ctypes.structure Ctypes.typ
type objc_protocol = Runtime__Type_description.Types.objc_protocol
val objc_protocol : objc_protocol Ctypes.structure Ctypes.typ
type class_t = objc_object Ctypes.structure Ctypes.ptr
type object_t = objc_object Ctypes.structure Ctypes.ptr
type imp_t = unit Ctypes.ptr
type selector_t = objc_selector Ctypes.structure Ctypes.ptr
type protocol_t = objc_object Ctypes.structure Ctypes.ptr
type ivar_t = objc_ivar Ctypes.structure Ctypes.ptr
type _Enc = string
module Method_description : sig ... end
module Property_attribute : sig ... end
val id : objc_object Ctypes.structure Ctypes_static.ptr Ctypes.typ
val _Class : objc_object Ctypes.structure Ctypes_static.ptr Ctypes.typ
val _SEL : objc_selector Ctypes.structure Ctypes_static.ptr Ctypes.typ
val _IMP : unit Ctypes_static.ptr Ctypes.typ
val _Enc : string Ctypes.typ
val _Protocol : objc_object Ctypes.structure Ctypes_static.ptr Ctypes.typ
val _Ivar : objc_ivar Ctypes.structure Ctypes_static.ptr Ctypes.typ
val _Method : objc_method Ctypes.structure Ctypes_static.ptr Ctypes.typ
type (!'a, !'b) pointer = ('a, 'b) Ctypes_static.pointer
type !'a ptr = ('a, [ `C ]) pointer
type !'a ocaml = 'a Ctypes_static.ocaml
type !'a carray = 'a Ctypes_static.carray
type !'a bigarray_class = 'a Ctypes_static.bigarray_class
val genarray : < ba_repr : 'b ; bigarray : ('a, 'b, 'l) Bigarray_compat.Genarray.t ; carray : 'a carray ; dims : int array ; element : 'a ; layout : 'l > bigarray_class
val array1 : < ba_repr : 'b ; bigarray : ('a, 'b, 'l) Bigarray_compat.Array1.t ; carray : 'a carray ; dims : int ; element : 'a ; layout : 'l > bigarray_class
val array2 : < ba_repr : 'b ; bigarray : ('a, 'b, 'l) Bigarray_compat.Array2.t ; carray : 'a carray carray ; dims : int * int ; element : 'a ; layout : 'l > bigarray_class
val array3 : < ba_repr : 'b ; bigarray : ('a, 'b, 'l) Bigarray_compat.Array3.t ; carray : 'a carray carray carray ; dims : int * int * int ; element : 'a ; layout : 'l > bigarray_class
type (!'a, !'kind) structured = ('a, 'kind) Ctypes_static.structured
type !'a structure = ('a, [ `Struct ]) structured
type !'a union = ('a, [ `Union ]) structured
type (!'a, !'t) field = ('a, 't) Ctypes_static.field
type !'a abstract = 'a Ctypes_static.abstract
type !'a typ = 'a Ctypes_static.typ
val void : unit typ
val char : char typ
val schar : int typ
val short : int typ
val int : int typ
val long : Signed.long typ
val llong : Signed.llong typ
val nativeint : nativeint typ
val int8_t : int typ
val int16_t : int typ
val int32_t : int32 typ
val int64_t : int64 typ
module Intptr = Ctypes.Intptr
val intptr_t : Intptr.t typ
module Ptrdiff = Ctypes.Ptrdiff
val ptrdiff_t : Ptrdiff.t typ
val camlint : int typ
val uchar : Unsigned.uchar typ
val bool : bool typ
val uint8_t : Unsigned.uint8 typ
val uint16_t : Unsigned.uint16 typ
val uint32_t : Unsigned.uint32 typ
val uint64_t : Unsigned.uint64 typ
val size_t : Unsigned.size_t typ
val ushort : Unsigned.ushort typ
val sint : Signed.sint typ
val uint : Unsigned.uint typ
val ulong : Unsigned.ulong typ
val ullong : Unsigned.ullong typ
module Uintptr = Ctypes.Uintptr
val uintptr_t : Uintptr.t typ
val float : float typ
val double : float typ
val ldouble : LDouble.t typ
val complex32 : Stdlib.Complex.t typ
val complex64 : Stdlib.Complex.t typ
val complexld : ComplexL.t typ
val ptr : 'a typ -> 'a Ctypes_static.ptr typ
val ptr_opt : 'a typ -> 'a Ctypes_static.ptr option typ
val string : string typ
val string_opt : string option typ
val ocaml_string : string Ctypes_static.ocaml typ
val ocaml_bytes : bytes Ctypes_static.ocaml typ
val array : int -> 'a typ -> 'a Ctypes_static.carray typ
val bigarray : < ba_repr : 'b ; bigarray : 'bigarray ; carray : 'c ; dims : 'dims ; element : 'a ; layout : Bigarray_compat.c_layout > Ctypes_static.bigarray_class -> 'dims -> ('a, 'b) Bigarray_compat.kind -> 'bigarray typ
val fortran_bigarray : < ba_repr : 'b ; bigarray : 'bigarray ; carray : 'c ; dims : 'dims ; element : 'a ; layout : Bigarray_compat.fortran_layout > Ctypes_static.bigarray_class -> 'dims -> ('a, 'b) Bigarray_compat.kind -> 'bigarray typ
val typ_of_bigarray_kind : ('a, 'b) Bigarray_compat.kind -> 'a typ
val structure : string -> 's Ctypes_static.structure typ
val union : string -> 's Ctypes_static.union typ
val field : ('s, [< `Struct | `Union ] as 'b) Ctypes_static.structured typ -> string -> 'a typ -> ('a, ('s, 'b) Ctypes_static.structured) field
val seal : ('a, [< `Struct | `Union ]) Ctypes_static.structured typ -> unit
val view : ?format_typ: ((Stdlib.Format.formatter -> unit) -> Stdlib.Format.formatter -> unit) -> ?format:(Stdlib.Format.formatter -> 'b -> unit) -> read:('a -> 'b) -> write:('b -> 'a) -> 'a typ -> 'b typ
val typedef : 'a typ -> string -> 'a typ
val abstract : name:string -> size:int -> alignment:int -> 'a Ctypes_static.abstract typ
val lift_typ : 'a Ctypes_static.typ -> 'a typ
type !'a fn = 'a Ctypes_static.fn
val (@->) : 'a typ -> 'b fn -> ('a -> 'b) fn
val returning : 'a typ -> 'a fn
type !'a static_funptr = 'a Ctypes_static.static_funptr
val static_funptr : 'a fn -> 'a Ctypes_static.static_funptr typ
val const : 'a typ -> 'a typ
val volatile : 'a typ -> 'a typ
val sizeof : 'a typ -> int
val alignment : 'a typ -> int
val format_typ : ?name:string -> Stdlib.Format.formatter -> 'a typ -> unit
val format_fn : ?name:string -> Stdlib.Format.formatter -> 'a fn -> unit
val string_of_typ : ?name:string -> 'a typ -> string
val string_of_fn : ?name:string -> 'a fn -> string
val format : 'a typ -> Stdlib.Format.formatter -> 'a -> unit
val string_of : 'a typ -> 'a -> string
val null : unit ptr
val (!@) : 'a ptr -> 'a
val (<-@) : 'a ptr -> 'a -> unit
val (+@) : ('a, 'b) pointer -> int -> ('a, 'b) pointer
val (-@) : ('a, 'b) pointer -> int -> ('a, 'b) pointer
val ptr_diff : ('a, 'b) pointer -> ('a, 'b) pointer -> int
val from_voidp : 'a typ -> unit ptr -> 'a ptr
val to_voidp : 'a ptr -> unit ptr
val allocate : ?finalise:('a ptr -> unit) -> 'a typ -> 'a -> 'a ptr
val allocate_n : ?finalise:('a ptr -> unit) -> 'a typ -> count:int -> 'a ptr
val ptr_compare : 'a ptr -> 'a ptr -> int
val is_null : 'a ptr -> bool
val reference_type : 'a ptr -> 'a typ
val ptr_of_raw_address : nativeint -> unit ptr
val funptr_of_raw_address : nativeint -> (unit -> unit) Ctypes_static.static_funptr
val raw_address_of_ptr : unit ptr -> nativeint
val string_from_ptr : char ptr -> length:int -> string
val ocaml_string_start : string -> string ocaml
val ocaml_bytes_start : bytes -> bytes ocaml
module CArray = Ctypes.CArray
val bigarray_start : < ba_repr : 'c ; bigarray : 'b ; carray : 'd ; dims : 'e ; element : 'a ; layout : 'l > bigarray_class -> 'b -> 'a ptr
val bigarray_of_ptr : < ba_repr : 'f ; bigarray : 'b ; carray : 'c ; dims : 'i ; element : 'a ; layout : Bigarray_compat.c_layout > bigarray_class -> 'i -> ('a, 'f) Bigarray_compat.kind -> 'a ptr -> 'b
val fortran_bigarray_of_ptr : < ba_repr : 'f ; bigarray : 'b ; carray : 'c ; dims : 'i ; element : 'a ; layout : Bigarray_compat.fortran_layout > bigarray_class -> 'i -> ('a, 'f) Bigarray_compat.kind -> 'a ptr -> 'b
val array_of_bigarray : < ba_repr : 'a ; bigarray : 'b ; carray : 'c ; dims : 'd ; element : 'e ; layout : Bigarray_compat.c_layout > bigarray_class -> 'b -> 'c
val bigarray_of_array : < ba_repr : 'f ; bigarray : 'b ; carray : 'c carray ; dims : 'i ; element : 'a ; layout : Bigarray_compat.c_layout > bigarray_class -> ('a, 'f) Bigarray_compat.kind -> 'c carray -> 'b
val make : ?finalise:(('a, 'b) structured -> unit) -> ('a, 'b) structured typ -> ('a, 'b) structured
val setf : ('b, 'c) structured -> ('a, ('b, 'c) structured) field -> 'a -> unit
val getf : ('b, 'c) structured -> ('a, ('b, 'c) structured) field -> 'a
val (@.) : ('b, 'c) structured -> ('a, ('b, 'c) structured) field -> 'a ptr
val (|->) : ('b, 'c) structured ptr -> ('a, ('b, 'c) structured) field -> 'a ptr
val offsetof : ('a, 'b structure) field -> int
val field_type : ('a, 'b) field -> 'a typ
val field_name : ('a, 'b) field -> string
val addr : ('a, 'b) structured -> ('a, 'b) structured ptr
val coerce : 'a typ -> 'b typ -> 'a -> 'b
val coerce_fn : 'a fn -> 'b fn -> 'a -> 'b
module type FOREIGN = Ctypes.FOREIGN
module type TYPE = Ctypes.TYPE
module Root = Ctypes.Root
exception Unsupported of string
exception ModifyingSealedType of string
exception IncompleteType
type uncoercible_info = Ctypes.uncoercible_info
exception Uncoercible of uncoercible_info
module UChar = Unsigned.UChar
module UInt8 = Unsigned.UInt8
module UInt16 = Unsigned.UInt16
module UInt32 = Unsigned.UInt32
module UInt64 = Unsigned.UInt64
module Size_t = Unsigned.Size_t
module UShort = Unsigned.UShort
module UInt = Unsigned.UInt
module ULong = Unsigned.ULong
module ULLong = Unsigned.ULLong
type uchar = UChar.t
type uint8 = UInt8.t
type uint16 = UInt16.t
type uint32 = UInt32.t
type uint64 = UInt64.t
type size_t = Size_t.t
type ushort = UShort.t
type uint = UInt.t
type ulong = ULong.t
type ullong = ULLong.t
module type Infix = Signed.Infix
module type S = Signed.S
module Int = Signed.Int
module Int32 = Signed.Int32
module Int64 = Signed.Int64
module SInt = Signed.SInt
module Long = Signed.Long
module LLong = Signed.LLong
type sint = SInt.t
type long = Long.t
type llong = LLong.t
val of_byte_size : int -> (module S)
module Objc_super : sig ... end
val msg_send : self:objc_object Ctypes.structure Ctypes_static.ptr -> cmd:objc_selector Ctypes.structure Ctypes_static.ptr -> typ:'a fn -> 'a
val msg_send_super : self: Runtime__.Type_description.Types.objc_object Ctypes.structure Ctypes_static.ptr -> cmd: Runtime__.Type_description.Types.objc_selector Ctypes.structure Ctypes_static.ptr -> typ:'a fn -> 'a
val msg_send_vo : self:objc_object Ctypes.structure Ctypes_static.ptr -> cmd:objc_selector Ctypes.structure Ctypes_static.ptr -> objc_object Ctypes.structure Ctypes_static.ptr
val msg_send_ov : self:objc_object Ctypes.structure Ctypes_static.ptr -> cmd:objc_selector Ctypes.structure Ctypes_static.ptr -> objc_object Ctypes.structure Ctypes_static.ptr -> unit
val msg_send_stret : self:objc_object Ctypes.structure Ctypes_static.ptr -> cmd:objc_selector Ctypes.structure Ctypes_static.ptr -> typ:'a fn -> return_type:'b typ -> 'a
val foreign_value_or_null : string -> 'a Ctypes.typ -> 'a Ctypes.ptr
val msg_send_suspended : self:object_t -> cmd:objc_selector Ctypes.structure Ctypes_static.ptr -> typ:'a fn -> 'a