| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Futhark.Optimise.ArrayShortCircuiting.DataStructs
Synopsis
- data Coalesced = Coalesced CoalescedKind ArrayMemBound FreeVarSubsts
- data CoalescedKind
- data ArrayMemBound = MemBlock {}
- type AllocTab = Map VName Space
- class HasMemBlock rep
- type ScalarTab = Map VName (PrimExp VName)
- type CoalsTab = Map VName CoalsEntry
- type ScopeTab rep = Scope (Aliases rep)
- data CoalsEntry = CoalsEntry {}
- type FreeVarSubsts = Map VName (TPrimExp Int64 VName)
- type LmadRef = LMAD (TPrimExp Int64 VName)
- data MemRefs = MemRefs {}
- data AccessSummary- = Undeterminable
- | Set (Set LmadRef)
 
- data BotUpEnv = BotUpEnv {}
- type InhibitTab = Map VName Names
- unionCoalsEntry :: CoalsEntry -> CoalsEntry -> CoalsEntry
- vnameToPrimExp :: AliasableRep rep => ScopeTab rep -> ScalarTab -> VName -> Maybe (PrimExp VName)
- getArrMemAssocFParam :: [Param FParamMem] -> [(VName, Uniqueness, ArrayMemBound)]
- getScopeMemInfo :: HasMemBlock rep => VName -> Scope rep -> Maybe ArrayMemBound
- createsNewArrOK :: Exp rep -> Bool
- getArrMemAssoc :: Pat (aliases, LetDecMem) -> [(VName, ArrayMemBound)]
- getUniqueMemFParam :: [Param FParamMem] -> Map VName Space
- markFailedCoal :: (CoalsTab, InhibitTab) -> VName -> (CoalsTab, InhibitTab)
- accessSubtract :: AccessSummary -> AccessSummary -> AccessSummary
- markSuccessCoal :: (CoalsTab, CoalsTab) -> VName -> CoalsEntry -> (CoalsTab, CoalsTab)
Documentation
Coalesced Access Entry
Constructors
| Coalesced | |
| Fields 
 | |
data CoalescedKind Source #
Constructors
| CopyCoal | let x = copy b^{lu} | 
| InPlaceCoal | let x[i] = b^{lu} | 
| ConcatCoal | let x = concat(a, b^{lu}) | 
| TransitiveCoal | transitive, i.e., other variables aliased with b. | 
| MapCoal | 
Instances
data ArrayMemBound Source #
Information about a memory block: type, shape, name and ixfun.
Instances
class HasMemBlock rep Source #
Minimal complete definition
Instances
| HasMemBlock (Aliases GPUMem) Source # | |
| Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs Methods getScopeMemInfo :: VName -> Scope (Aliases GPUMem) -> Maybe ArrayMemBound Source # | |
| HasMemBlock (Aliases MCMem) Source # | |
| Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs Methods getScopeMemInfo :: VName -> Scope (Aliases MCMem) -> Maybe ArrayMemBound Source # | |
| HasMemBlock (Aliases SeqMem) Source # | |
| Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs Methods getScopeMemInfo :: VName -> Scope (Aliases SeqMem) -> Maybe ArrayMemBound Source # | |
type ScalarTab = Map VName (PrimExp VName) Source #
maps a variable name to its PrimExp scalar expression
type CoalsTab = Map VName CoalsEntry Source #
maps a memory-block name to a CoalsEntry. Among other things, it contains
   vartab, a map in which each variable associated to that memory block is
   bound to its Coalesced info.
type ScopeTab rep = Scope (Aliases rep) Source #
maps array-variable names to various info, including types, memory block and index function, etc.
data CoalsEntry Source #
Constructors
| CoalsEntry | |
| Fields 
 | |
Instances
type LmadRef = LMAD (TPrimExp Int64 VName) Source #
An LMAD specialized to TPrimExps (a typed primexp)
Constructors
| MemRefs | |
| Fields 
 | |
data AccessSummary Source #
Summary of all memory accesses at a given point in the code
Constructors
| Undeterminable | The access summary was statically undeterminable, for instance by having multiple lmads. In this case, we should conservatively avoid all coalescing. | 
| Set (Set LmadRef) | A conservative estimate of the set of accesses up until this point. | 
Instances
| Monoid AccessSummary Source # | |
| Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs Methods mempty :: AccessSummary # mappend :: AccessSummary -> AccessSummary -> AccessSummary # mconcat :: [AccessSummary] -> AccessSummary # | |
| Semigroup AccessSummary Source # | |
| Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs Methods (<>) :: AccessSummary -> AccessSummary -> AccessSummary # sconcat :: NonEmpty AccessSummary -> AccessSummary # stimes :: Integral b => b -> AccessSummary -> AccessSummary # | |
| FreeIn AccessSummary Source # | |
| Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs Methods freeIn' :: AccessSummary -> FV Source # | |
| Pretty AccessSummary Source # | |
Constructors
| BotUpEnv | |
| Fields 
 | |
type InhibitTab = Map VName Names Source #
inhibited memory-block mergings from the key (memory block) to the value (set of memory blocks).
unionCoalsEntry :: CoalsEntry -> CoalsEntry -> CoalsEntry Source #
Compute the union of two CoalsEntry. If two CoalsEntry do not refer to
 the same destination memory and use the same index function, the first
 CoalsEntry is returned.
vnameToPrimExp :: AliasableRep rep => ScopeTab rep -> ScalarTab -> VName -> Maybe (PrimExp VName) Source #
getArrMemAssocFParam :: [Param FParamMem] -> [(VName, Uniqueness, ArrayMemBound)] Source #
Get the names of arrays in a list of FParam and the corresponding
 ArrayMemBound information for each array.
getScopeMemInfo :: HasMemBlock rep => VName -> Scope rep -> Maybe ArrayMemBound Source #
Looks up VName in the given scope. If it is a MemArray, return the
 ArrayMemBound information for the array.
createsNewArrOK :: Exp rep -> Bool Source #
True if the expression returns a "fresh" array.
getArrMemAssoc :: Pat (aliases, LetDecMem) -> [(VName, ArrayMemBound)] Source #
Get the names of array PatElems in a Pat and the corresponding
 ArrayMemBound information for each array.
markFailedCoal :: (CoalsTab, InhibitTab) -> VName -> (CoalsTab, InhibitTab) Source #
Memory-block removal from active-coalescing table
   should only be handled via this function, it is easy
   to run into infinite execution problem; i.e., the
   fix-pointed iteration of coalescing transformation
   assumes that whenever a coalescing fails it is
   recorded in the inhibit table.
markSuccessCoal :: (CoalsTab, CoalsTab) -> VName -> CoalsEntry -> (CoalsTab, CoalsTab) Source #
promotion from active-to-successful coalescing tables should be handled with this function (for clarity).