plugins-multistage-0.6.3: Dynamic linking for embedded DSLs with staged compilation

Safe HaskellNone
LanguageHaskell2010

System.Plugins.MultiStage

Contents

Description

Generic components

Synopsis

Loading

loadFunWithConfig :: Config -> [Name] -> Q [Dec] Source #

Generic function compiler and loader

loadFunType :: Name -> Q Type Source #

Extract the type of the supplied function name

Configuration

data Config Source #

Configuration parameters for the function loader

Constructors

Config 

Fields

defaultBuilder :: Config -> Name -> Q Body Source #

Build, load and link a C file

Calling Convention

data CallConv Source #

The Calling Convention specifies how a type should be converted

Constructors

CallConv 

Fields

buildType :: CallConv -> Type -> Q Type Source #

Convert a type using the supplied calling convention

applyTF :: Name -> Type -> Q Type Source #

Apply a type family

expandTF :: Type -> Q Type Source #

Expand type families

Marshaling

pack :: (Reference (Rep a), Marshal a) => a -> IO (Ref (Rep a)) Source #

Pack a value into its runtime representation

pack a = to a >>= ref

unpack :: (Reference (Rep a), Marshal a) => Ref (Rep a) -> IO a Source #

Unpack a value from its runtime representation

unpack a = deref a >>= from

class Reference a where Source #

Optionally make a refrence of a value

Minimal complete definition

Nothing

Associated Types

type Ref a :: * Source #

The type of a referenced value

Methods

ref :: a -> IO (Ref a) Source #

Convert to a referenced value

ref :: a ~ Ref a => a -> IO (Ref a) Source #

Convert to a referenced value

deref :: Ref a -> IO a Source #

Convert from a referenced value In the IO monad to allow peeking through the reference.

deref :: a ~ Ref a => Ref a -> IO a Source #

Convert from a referenced value In the IO monad to allow peeking through the reference.

Instances
Reference Bool Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Bool :: Type Source #

Methods

ref :: Bool -> IO (Ref Bool) Source #

deref :: Ref Bool -> IO Bool Source #

Reference Double Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Double :: Type Source #

Reference Float Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Float :: Type Source #

Reference Int8 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Int8 :: Type Source #

Methods

ref :: Int8 -> IO (Ref Int8) Source #

deref :: Ref Int8 -> IO Int8 Source #

Reference Int16 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Int16 :: Type Source #

Reference Int32 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Int32 :: Type Source #

Reference Int64 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Int64 :: Type Source #

Reference Word8 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Word8 :: Type Source #

Reference Word16 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Word16 :: Type Source #

Reference Word32 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Word32 :: Type Source #

Reference Word64 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Ref Word64 :: Type Source #

class Marshal a where Source #

Convert between Haskell and representation types

Minimal complete definition

Nothing

Associated Types

type Rep a :: * Source #

Methods

to :: a -> IO (Rep a) Source #

to :: a ~ Rep a => a -> IO (Rep a) Source #

from :: Rep a -> IO a Source #

from :: a ~ Rep a => Rep a -> IO a Source #

Instances
Marshal Bool Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Bool :: Type Source #

Methods

to :: Bool -> IO (Rep Bool) Source #

from :: Rep Bool -> IO Bool Source #

Marshal Double Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Double :: Type Source #

Marshal Float Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Float :: Type Source #

Marshal Int8 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Int8 :: Type Source #

Methods

to :: Int8 -> IO (Rep Int8) Source #

from :: Rep Int8 -> IO Int8 Source #

Marshal Int16 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Int16 :: Type Source #

Marshal Int32 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Int32 :: Type Source #

Marshal Int64 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Int64 :: Type Source #

Marshal Word8 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Word8 :: Type Source #

Marshal Word16 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Word16 :: Type Source #

Marshal Word32 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Word32 :: Type Source #

Marshal Word64 Source # 
Instance details

Defined in System.Plugins.MultiStage

Associated Types

type Rep Word64 :: Type Source #