language-c-inline-0.7.7.0: Inline C & Objective-C code in Haskell for language interoperability

Portabilitynon-portable (GHC extensions)
Stabilityexperimental
MaintainerManuel M T Chakravarty <chak@cse.unsw.edu.au>
Safe HaskellNone

Language.C.Inline.ObjC

Contents

Description

This module exports the principal API for inline Objective-C.

Synopsis

Re-export types from C

type CString = Ptr CChar

type CStringLen = (Ptr CChar, Int)

type CWString = Ptr CWchar

type CWStringLen = (Ptr CWchar, Int)

data Errno

Instances

Eq Errno 

data ForeignPtr a

Instances

Typeable1 ForeignPtr 
Eq (ForeignPtr a) 
Typeable a => Data (ForeignPtr a) 
Ord (ForeignPtr a) 
Show (ForeignPtr a) 

Re-export types from Template Haskell

data Name

Instances

Eq Name 
Data Name 
Ord Name 
Show Name 
Typeable Name 
Lift Name 
Ppr Name 
IsType Name 

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.)

objc_recordSource

Arguments

:: 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

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_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 ExpSource

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.

objc_emit :: Q [Dec]Source

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 whereSource

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.

Constructors

:> :: Hint hint => e -> hint -> Annotated e 
Typed :: Name -> Annotated Name 

(<:) :: Hint hint => hint -> e -> Annotated eSource

We provide additional syntax where the hint is to the left of the annotated entity.

void :: e -> Annotated eSource

Annotation for irrelevant results

data Class whereSource

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.

Constructors

Class :: IsType t => t -> Class 

class IsType ty Source

Class of entities that can be used as TH types.

Instances

IsType Type 
IsType Name 
IsType (Q Type) 

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) -> PropertyAccessSource

Map a property to explicit projection and update functions.

(-->) :: ObjCIfaceDecl -> Name -> PropertyAccessSource

Map a property to a field label. This function assumes that the field name is typed and can be reified.