Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- extractAllocations :: MCCode -> (MCCode, MCCode)
- compileThreadResult :: SegSpace -> PatElem LetDecMem -> KernelResult -> MulticoreGen ()
- data Locks = Locks {
- locksArray :: VName
- locksCount :: Int
- data HostEnv = HostEnv {}
- type AtomicBinOp = BinOp -> Maybe (VName -> VName -> Count Elements (TExp Int32) -> Exp -> AtomicOp)
- type MulticoreGen = ImpM MCMem HostEnv Multicore
- decideScheduling :: MCCode -> Scheduling
- decideScheduling' :: SegOp () rep -> MCCode -> Scheduling
- renameSegBinOp :: [SegBinOp MCMem] -> MulticoreGen [SegBinOp MCMem]
- freeParams :: FreeIn a => a -> MulticoreGen [Param]
- renameHistOpLambda :: [HistOp MCMem] -> MulticoreGen [HistOp MCMem]
- atomicUpdateLocking :: AtomicBinOp -> Lambda MCMem -> AtomicUpdate MCMem ()
- data AtomicUpdate rep r
- = AtomicPrim (DoAtomicUpdate rep r)
- | AtomicCAS (DoAtomicUpdate rep r)
- | AtomicLocking (Locking -> DoAtomicUpdate rep r)
- type DoAtomicUpdate rep r = [VName] -> [TExp Int64] -> MulticoreGen ()
- data Locking = Locking {
- lockingArray :: VName
- lockingIsUnlocked :: TExp Int32
- lockingToLock :: TExp Int32
- lockingToUnlock :: TExp Int32
- lockingMapping :: [TExp Int64] -> [TExp Int64]
- getSpace :: SegOp () MCMem -> SegSpace
- getLoopBounds :: MulticoreGen (TExp Int64, TExp Int64)
- getIterationDomain :: SegOp () MCMem -> SegSpace -> MulticoreGen (TExp Int64)
- getReturnParams :: Pat LetDecMem -> SegOp () MCMem -> MulticoreGen [Param]
- segOpString :: SegOp () MCMem -> MulticoreGen String
- data ChunkLoopVectorization
- = Vectorized
- | Scalar
- generateChunkLoop :: String -> ChunkLoopVectorization -> (TExp Int64 -> MulticoreGen ()) -> MulticoreGen ()
- generateUniformizeLoop :: (TExp Int64 -> MulticoreGen ()) -> MulticoreGen ()
- extractVectorLane :: TExp Int64 -> MulticoreGen MCCode -> MulticoreGen ()
- inISPC :: MulticoreGen () -> MulticoreGen ()
- toParam :: VName -> TypeBase shape u -> MulticoreGen [Param]
- sLoopNestVectorized :: Shape -> ([TExp Int64] -> MulticoreGen ()) -> MulticoreGen ()
Documentation
compileThreadResult :: SegSpace -> PatElem LetDecMem -> KernelResult -> MulticoreGen () Source #
Information about the locks available for accumulators.
Locks | |
|
type AtomicBinOp = BinOp -> Maybe (VName -> VName -> Count Elements (TExp Int32) -> Exp -> AtomicOp) Source #
decideScheduling :: MCCode -> Scheduling Source #
decideScheduling' :: SegOp () rep -> MCCode -> Scheduling Source #
renameSegBinOp :: [SegBinOp MCMem] -> MulticoreGen [SegBinOp MCMem] Source #
freeParams :: FreeIn a => a -> MulticoreGen [Param] Source #
renameHistOpLambda :: [HistOp MCMem] -> MulticoreGen [HistOp MCMem] Source #
atomicUpdateLocking :: AtomicBinOp -> Lambda MCMem -> AtomicUpdate MCMem () Source #
data AtomicUpdate rep r Source #
The mechanism that will be used for performing the atomic update. Approximates how efficient it will be. Ordered from most to least efficient.
AtomicPrim (DoAtomicUpdate rep r) | |
AtomicCAS (DoAtomicUpdate rep r) | Can be done by efficient swaps. |
AtomicLocking (Locking -> DoAtomicUpdate rep r) | Requires explicit locking. |
type DoAtomicUpdate rep r = [VName] -> [TExp Int64] -> MulticoreGen () Source #
A function for generating code for an atomic update. Assumes that the bucket is in-bounds.
Locking strategy used for an atomic update.
Locking | |
|
getLoopBounds :: MulticoreGen (TExp Int64, TExp Int64) Source #
getIterationDomain :: SegOp () MCMem -> SegSpace -> MulticoreGen (TExp Int64) Source #
getReturnParams :: Pat LetDecMem -> SegOp () MCMem -> MulticoreGen [Param] Source #
segOpString :: SegOp () MCMem -> MulticoreGen String Source #
data ChunkLoopVectorization Source #
Indicates whether to vectorize a chunk loop or keep it sequential. We use this to allow falling back to sequential chunk loops in cases we don't care about trying to vectorize.
generateChunkLoop :: String -> ChunkLoopVectorization -> (TExp Int64 -> MulticoreGen ()) -> MulticoreGen () Source #
Emit code for the chunk loop, given an action that generates code for a single iteration.
The action is called with the (symbolic) index of the current iteration.
generateUniformizeLoop :: (TExp Int64 -> MulticoreGen ()) -> MulticoreGen () Source #
Emit code for a sequential loop over each vector lane, given and action that generates code for a single iteration. The action is called with the symbolic index of the current iteration.
extractVectorLane :: TExp Int64 -> MulticoreGen MCCode -> MulticoreGen () Source #
Given a piece of code, if that code performs an assignment, turn that assignment into an extraction of element from a vector on the right hand side, using a passed index for the extraction. Other code is left as is.
inISPC :: MulticoreGen () -> MulticoreGen () Source #
Given an action that may generate some code, put that code into an ISPC kernel.
sLoopNestVectorized :: Shape -> ([TExp Int64] -> MulticoreGen ()) -> MulticoreGen () Source #
Like sLoopNest, but puts a vectorized loop at the innermost layer.