accelerate-llvm-native-1.1.0.1: Accelerate backend for multicore CPUs

Copyright[2016..2017] Trevor L. McDonell
LicenseBSD3
MaintainerTrevor L. McDonell <tmcdonell@cse.unsw.edu.au>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Array.Accelerate.LLVM.Native.Foreign

Contents

Description

 

Synopsis

Documentation

data ForeignAcc f where Source #

Constructors

ForeignAcc :: String -> (a -> LLVM Native b) -> ForeignAcc (a -> b) 

Instances

Foreign ForeignAcc Source # 

Methods

strForeign :: ForeignAcc args -> String

liftForeign :: ForeignAcc args -> Q (TExp (ForeignAcc args))

data ForeignExp f where Source #

Constructors

ForeignExp :: String -> IRFun1 Native () (x -> y) -> ForeignExp (x -> y) 

Instances

Foreign ForeignExp Source # 

Methods

strForeign :: ForeignExp args -> String

liftForeign :: ForeignExp args -> Q (TExp (ForeignExp args))

data LLVM target a :: * -> * -> * #

The LLVM monad, for executing array computations. This consists of a stack for the LLVM execution context as well as the per-execution target specific state target.

Instances

MonadState target (LLVM target) 

Methods

get :: LLVM target target #

put :: target -> LLVM target () #

state :: (target -> (a, target)) -> LLVM target a #

Execute arch => ExecuteAfun arch (LLVM arch b) 

Associated Types

type ExecAfunR arch (LLVM arch b) :: *

Methods

executeOpenAfun :: ExecOpenAfun arch aenv (ExecAfunR arch (LLVM arch b)) -> LLVM arch (AvalR arch aenv) -> LLVM arch b

Monad (LLVM target) 

Methods

(>>=) :: LLVM target a -> (a -> LLVM target b) -> LLVM target b #

(>>) :: LLVM target a -> LLVM target b -> LLVM target b #

return :: a -> LLVM target a #

fail :: String -> LLVM target a #

Functor (LLVM target) 

Methods

fmap :: (a -> b) -> LLVM target a -> LLVM target b #

(<$) :: a -> LLVM target b -> LLVM target a #

Applicative (LLVM target) 

Methods

pure :: a -> LLVM target a #

(<*>) :: LLVM target (a -> b) -> LLVM target a -> LLVM target b #

liftA2 :: (a -> b -> c) -> LLVM target a -> LLVM target b -> LLVM target c #

(*>) :: LLVM target a -> LLVM target b -> LLVM target b #

(<*) :: LLVM target a -> LLVM target b -> LLVM target a #

MonadIO (LLVM target) 

Methods

liftIO :: IO a -> LLVM target a #

MonadThrow (LLVM target) 

Methods

throwM :: Exception e => e -> LLVM target a #

MonadCatch (LLVM target) 

Methods

catch :: Exception e => LLVM target a -> (e -> LLVM target a) -> LLVM target a #

MonadMask (LLVM target) 

Methods

mask :: ((forall a. LLVM target a -> LLVM target a) -> LLVM target b) -> LLVM target b #

uninterruptibleMask :: ((forall a. LLVM target a -> LLVM target a) -> LLVM target b) -> LLVM target b #

type ExecAfunR arch (LLVM arch b) 
type ExecAfunR arch (LLVM arch b) = b

data Native Source #

Native machine code JIT execution target

Constructors

Native 

Fields

Instances

Target Native Source # 
data ExecutableR Native 
data ExecutableR Native = NativeR {}
data ObjectR Native 
type ArgR Native 
type ArgR Native = Arg
type EventR Native 
type EventR Native = ()
type StreamR Native 
type StreamR Native = ()
data KernelMetadata Native 
data KernelMetadata Native = KM_Native ()

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

cloneArray :: (Shape sh, Elt e) => Array sh e -> LLVM Native (Array sh e) Source #

Copy an array into a newly allocated array. This uses memcpy.

Orphan instances

Foreign Native Source # 

Methods

foreignAcc :: (Foreign asm, Typeable * a, Typeable * b) => Native -> asm (a -> b) -> Maybe (StreamR Native -> a -> LLVM Native b)

foreignExp :: (Foreign asm, Typeable * x, Typeable * y) => Native -> asm (x -> y) -> Maybe (IRFun1 Native () (x -> y))