| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Futhark.CodeGen.ImpGen.Multicore.Base
Synopsis
- extractAllocations :: Code -> (Code, Code)
- compileThreadResult :: SegSpace -> PatElem MCMem -> KernelResult -> MulticoreGen ()
- newtype HostEnv = HostEnv {}
- type AtomicBinOp = BinOp -> Maybe (VName -> VName -> Count Elements (TExp Int32) -> Exp -> AtomicOp)
- type MulticoreGen = ImpM MCMem HostEnv Multicore
- decideScheduling :: Code -> Scheduling
- decideScheduling' :: SegOp () lore -> Code -> Scheduling
- groupResultArrays :: String -> SubExp -> [SegBinOp MCMem] -> MulticoreGen [[VName]]
- renameSegBinOp :: [SegBinOp MCMem] -> MulticoreGen [SegBinOp MCMem]
- freeParams :: Code -> [VName] -> MulticoreGen [Param]
- renameHistOpLambda :: [HistOp MCMem] -> MulticoreGen [HistOp MCMem]
- atomicUpdateLocking :: AtomicBinOp -> Lambda MCMem -> AtomicUpdate MCMem ()
- data AtomicUpdate lore r- = AtomicPrim (DoAtomicUpdate lore r)
- | AtomicCAS (DoAtomicUpdate lore r)
- | AtomicLocking (Locking -> DoAtomicUpdate lore r)
 
- data Locking = Locking {- lockingArray :: VName
- lockingIsUnlocked :: TExp Int32
- lockingToLock :: TExp Int32
- lockingToUnlock :: TExp Int32
- lockingMapping :: [TExp Int64] -> [TExp Int64]
 
- getSpace :: SegOp () MCMem -> SegSpace
- getIterationDomain :: SegOp () MCMem -> SegSpace -> MulticoreGen (TExp Int64)
- getReturnParams :: Pattern MCMem -> SegOp () MCMem -> MulticoreGen [Param]
- segOpString :: SegOp () MCMem -> MulticoreGen String
Documentation
compileThreadResult :: SegSpace -> PatElem MCMem -> KernelResult -> MulticoreGen () Source #
Constructors
| HostEnv | |
| Fields | |
type AtomicBinOp = BinOp -> Maybe (VName -> VName -> Count Elements (TExp Int32) -> Exp -> AtomicOp) Source #
decideScheduling :: Code -> Scheduling Source #
decideScheduling' :: SegOp () lore -> Code -> Scheduling Source #
groupResultArrays :: String -> SubExp -> [SegBinOp MCMem] -> MulticoreGen [[VName]] Source #
Arrays for storing group results shared between threads
renameSegBinOp :: [SegBinOp MCMem] -> MulticoreGen [SegBinOp MCMem] Source #
freeParams :: Code -> [VName] -> MulticoreGen [Param] Source #
renameHistOpLambda :: [HistOp MCMem] -> MulticoreGen [HistOp MCMem] Source #
atomicUpdateLocking :: AtomicBinOp -> Lambda MCMem -> AtomicUpdate MCMem () Source #
data AtomicUpdate lore 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.
Constructors
| AtomicPrim (DoAtomicUpdate lore r) | |
| AtomicCAS (DoAtomicUpdate lore r) | Can be done by efficient swaps. | 
| AtomicLocking (Locking -> DoAtomicUpdate lore r) | Requires explicit locking. | 
Locking strategy used for an atomic update.
Constructors
| Locking | |
| Fields 
 | |
getIterationDomain :: SegOp () MCMem -> SegSpace -> MulticoreGen (TExp Int64) Source #
getReturnParams :: Pattern MCMem -> SegOp () MCMem -> MulticoreGen [Param] Source #
segOpString :: SegOp () MCMem -> MulticoreGen String Source #