Copyright | [2013..2016] Manuel M T Chakravarty |
---|---|
License | BSD3 |
Maintainer | Manuel M T Chakravarty <chak@cse.unsw.edu.au> |
Stability | experimental |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell98 |
This module exports the principal API for inline Objective-C.
- module Foreign.C.Types
- type CString = Ptr CChar
- type CStringLen = (Ptr CChar, Int)
- type CWString = Ptr CWchar
- type CWStringLen = (Ptr CWchar, Int)
- data Errno :: *
- data ForeignPtr a :: * -> *
- castForeignPtr :: ForeignPtr a -> ForeignPtr b
- data Name :: *
- objc_retain :: Ptr a -> IO (Ptr a)
- objc_release :: Ptr a -> IO ()
- objc_release_ptr :: FunPtr (Ptr a -> IO ())
- newForeignClassPtr :: Ptr a -> IO (ForeignPtr a)
- newForeignStructPtr :: Ptr a -> IO (ForeignPtr a)
- objc_import :: [FilePath] -> Q [Dec]
- objc_interface :: [Definition] -> Q [Dec]
- objc_implementation :: [Annotated Name] -> [Definition] -> Q [Dec]
- objc_record :: String -> String -> Name -> [Annotated Name] -> [PropertyAccess] -> [ObjCIfaceDecl] -> [Definition] -> Q [Dec]
- objc_marshaller :: Name -> Name -> Q [Dec]
- objc_class_marshaller :: Name -> Name -> Q [Dec]
- objc_struct_marshaller :: Name -> Name -> Q [Dec]
- objc_typecheck :: Q [Dec]
- objc :: [Annotated Name] -> Annotated Exp -> Q Exp
- objc_emit :: Q [Dec]
- data Annotated e where
- (<:) :: Hint hint => hint -> e -> Annotated e
- void :: e -> Annotated e
- data Class where
- data Struct where
- class IsType ty
- data PropertyAccess
- (==>) :: ObjCIfaceDecl -> (TypeQ, ExpQ, ExpQ) -> PropertyAccess
- (-->) :: ObjCIfaceDecl -> Name -> PropertyAccess
Re-export types from C
module Foreign.C.Types
type CStringLen = (Ptr CChar, Int) #
A string with explicit length information in bytes instead of a terminating NUL (allowing NUL characters in the middle of the string).
A C wide string is a reference to an array of C wide characters terminated by NUL.
type CWStringLen = (Ptr CWchar, Int) #
A wide character string with explicit length information in CWchar
s
instead of a terminating NUL (allowing NUL characters in the middle
of the string).
Haskell representation for errno
values.
The implementation is deliberately exposed, to allow users to add
their own definitions of Errno
values.
data ForeignPtr a :: * -> * #
The type ForeignPtr
represents references to objects that are
maintained in a foreign language, i.e., that are not part of the
data structures usually managed by the Haskell storage manager.
The essential difference between ForeignPtr
s and vanilla memory
references of type Ptr a
is that the former may be associated
with finalizers. A finalizer is a routine that is invoked when
the Haskell storage manager detects that - within the Haskell heap
and stack - there are no more references left that are pointing to
the ForeignPtr
. Typically, the finalizer will, then, invoke
routines in the foreign language that free the resources bound by
the foreign object.
The ForeignPtr
is parameterised in the same way as Ptr
. The
type argument of ForeignPtr
should normally be an instance of
class Storable
.
Eq (ForeignPtr a) | |
Ord (ForeignPtr a) | |
Show (ForeignPtr a) | |
castForeignPtr :: ForeignPtr a -> ForeignPtr b #
This function casts a ForeignPtr
parameterised by one type into another type.
Re-export types from Template Haskell
An abstract type representing names in the syntax tree.
Name
s can be constructed in several ways, which come with different
name-capture guarantees (see Language.Haskell.TH.Syntax for
an explanation of name capture):
- the built-in syntax
'f
and''T
can be used to construct names, The expression'f
gives aName
which refers to the valuef
currently in scope, and''T
gives aName
which refers to the typeT
currently in scope. These names can never be captured. lookupValueName
andlookupTypeName
are similar to'f
and''T
respectively, but theName
s are looked up at the point where the current splice is being run. These names can never be captured.newName
monadically generates a new name, which can never be captured.mkName
generates a capturable name.
Names constructed using newName
and mkName
may be used in bindings
(such as let x = ...
or x -> ...
), but names constructed using
lookupValueName
, lookupTypeName
, 'f
, ''T
may not.
Objective-C memory management support
objc_release :: Ptr a -> IO () Source #
newForeignClassPtr :: Ptr a -> IO (ForeignPtr a) Source #
Turn a retainable Objective-C pointer into a foreign pointer that is released when finalised.
NB: We need to retain the pointer first as it won't come with a +1 retain count for Haskell land to consume (at best, it will have an autoreleased +1 if it is a function return result).
newForeignStructPtr :: Ptr a -> IO (ForeignPtr a) Source #
Turn a non-retainable C pointer into a foreign pointer that is freed when finalised.
Combinators for inline Objective-C
objc_import :: [FilePath] -> Q [Dec] Source #
Specify imported Objective-C files. Needs to be spliced where an import declaration can appear. (Just put it straight after all the import statements in the module.)
NB: This inline splice must appear before any other use of inline code in a module.
FIXME: need to use TH.addDependentFile on each of the imported ObjC files & read headers
objc_interface :: [Definition] -> Q [Dec] Source #
Inline Objective-C top-level definitions for a header file ('.h').
objc_implementation :: [Annotated Name] -> [Definition] -> Q [Dec] Source #
Inline Objective-C top-level definitions for an implementation file ('.m').
The top-level Haskell variables given in the first argument will be foreign exported to be accessed from the generated Objective-C code. In C, these Haskell variables will always be represented as functions. (In particular, if the Haskell variable refers to a CAF, it will be a nullary function in C — after all, a thunk may still need to be evaluated.)
:: String | prefix of the class name |
-> String | class name |
-> Name | name of the Haskell type of the bridged Haskell structure |
-> [Annotated Name] | Haskell variables used in Objective-C code |
-> [PropertyAccess] | Objective-C properties with corresponding Haskell projections and update functions |
-> [ObjCIfaceDecl] | extra interface declarations |
-> [Definition] | extra implementation declarations |
-> Q [Dec] |
Specification of a bridge for a Haskell structure that can be queried and updated from Objective-C.
The first argument is the name of the Objective-C class that will be a proxy for the Haskell structure. The second argument the name of the Haskell type of the bridged Haskell structure.
The generated class is immutable. When a property is updated, a new instance is allocated. This closely mirrors the behaviour of the Haskell structure for which the class is a proxy.
The designated initialiser of the generated class is '[-initWithHsNameHsPtr:(HsStablePtr)particleHsPtr]',
where '<HsName>' is the type name of the Haskell structure. This initialiser is generated if it is not
explicitly provided. The generated method '[-init]' calls the designated initialiser with nil
for the
stable pointer.
WARNING: This is a very experimental feature and it will SURELY change in the future!!!
FIXME: don't generate the designated initialiser if it is explicitly provided
objc_marshaller :: Name -> Name -> Q [Dec] Source #
Deprecated: use objc_class_marshaller
or objc_struct_marshaller
instead
Deprecated: use objc_class_marshaller
or objc_struct_marshaller
instead
objc_class_marshaller :: Name -> Name -> Q [Dec] Source #
Declare a Haskell-Objective-C marshaller pair to be used in all subsequent marshalling code generation.
On the Objective-C side, the marshallers must use a wrapped foreign pointer to an Objective-C class (just as those
of Class
hints). The domain and codomain of the two marshallers must be the opposite and both are executing in IO
.
objc_struct_marshaller :: Name -> Name -> Q [Dec] Source #
Declare a Haskell-Objective-C marshaller pair to be used in all subsequent marshalling code generation.
On the Objective-C side, the marshallers must use a wrapped foreign pointer to an C struct (just as those
of Struct
hints). The domain and codomain of the two marshallers must be the opposite and both are executing in IO
.
objc_typecheck :: Q [Dec] Source #
Force type checking of all declaration appearing earlier in this module.
Template Haskell performs type checking on declaration groups seperated by toplevel splices. In order for a type
declaration to be available to an Objective-C inline directive, the type declaration must be in an earlier
declaration group than the Objective-C inline directive. A toplevel Objective-C inline directive always is the start
of a new declaration group; hence, it can be considered to be implicitly preceded by an objc_typecheck
.
objc :: [Annotated Name] -> Annotated Exp -> Q Exp Source #
Inline Objective-C expression.
The inline expression will be wrapped in a C function whose arguments are marshalled versions of the Haskell variables given in the first argument. The marshalling of the variables and of the result is determined by the marshalling annotations at the variables and the inline expression.
Emit the Objective-C file and return the foreign declarations. Needs to be the last use of an 'objc...' function. (Just put it at the end of the Haskell module.)
Marshalling annotations
data Annotated e where Source #
Annotating entities with hints.
The alternatives are to provide an explicit marshalling hint with '(:>)', or to leave the marshalling implicitly defined by the name's type.
(<:) :: Hint hint => hint -> e -> Annotated e Source #
We provide additional syntax where the hint is to the left of the annotated entity.
Hint indicating to marshal an Objective-C object as a foreign pointer, where the argument is the Haskell type representing the Objective-C class. The Haskell type name must coincide with the Objective-C class name.
Hint indicating to marshal a pointer to a C struct as a foreign pointer, where the argument is the Haskell type representing the C type name. The Haskell type name must coincide with the C type name.
NB: This is like Class
with the difference that finalisers on foreign pointers created during marshalling use
free
rather than release
.
Class of entities that can be used as TH types.
theType
Property maps
data PropertyAccess Source #
Maps a quoted property to a quoted projection and a quoted update function in addition to the type of the projected value.
(==>) :: ObjCIfaceDecl -> (TypeQ, ExpQ, ExpQ) -> PropertyAccess Source #
Map a property to explicit projection and update functions.
(-->) :: ObjCIfaceDecl -> Name -> PropertyAccess Source #
Map a property to a field label. This function assumes that the field name is typed and can be reified.