futhark-0.24.3: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.Optimise.ArrayShortCircuiting.DataStructs

Synopsis

Documentation

data Coalesced Source #

Coalesced Access Entry

Constructors

Coalesced 

Fields

  • CoalescedKind

    the kind of coalescing

  • ArrayMemBound

    destination mem_block info f_m_x[i] (must be ArrayMem) (Maybe IxFun) -- the inverse ixfun of a coalesced array, such that -- ixfuns can be correctly constructed for aliases;

  • FreeVarSubsts

    substitutions for free vars in index function

Instances

Instances details
Pretty Coalesced Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: Coalesced -> Doc ann #

prettyList :: [Coalesced] -> Doc ann #

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

Instances details
Pretty CoalescedKind Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: CoalescedKind -> Doc ann #

prettyList :: [CoalescedKind] -> Doc ann #

data ArrayMemBound Source #

Information about a memory block: type, shape, name and ixfun.

Constructors

MemBlock 

Instances

Instances details
Pretty ArrayMemBound Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: ArrayMemBound -> Doc ann #

prettyList :: [ArrayMemBound] -> Doc ann #

type AllocTab = Map VName Space Source #

the allocatted memory blocks

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

  • dstmem :: VName

    destination memory block

  • dstind :: IxFun

    index function of the destination (used for rebasing)

  • alsmem :: Names

    aliased destination memory blocks can appear due to repeated (optimistic) coalescing.

  • vartab :: Map VName Coalesced

    per variable-name coalesced entries

  • optdeps :: Map VName VName

    keys are variable names, values are memblock names; it records optimistically added coalesced nodes, e.g., in the case of if-then-else expressions. For example: x = map f a .. use of y .. b = map g a x[i] = b y[k] = x the coalescing of b in x[i] succeeds, but is dependent of the success of the coalescing of x in y[k], which fails in this case because y is used before the new array creation of x = map f. Hence optdeps of the m_b CoalsEntry records x -> m_x and at the end of analysis it is removed from the successfully coalesced table if m_x is unsuccessful. Storing m_x would probably be sufficient if memory would not be reused--e.g., by register allocation on arrays--the x discriminates between memory being reused across semantically different arrays (searched in vartab field).

  • memrefs :: MemRefs

    Access summaries of uses and writes of destination and source respectively.

Instances

Instances details
Pretty CoalsEntry Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: CoalsEntry -> Doc ann #

prettyList :: [CoalsEntry] -> Doc ann #

Pretty CoalsTab Source # 
Instance details

Defined in Futhark.Optimise.ArrayShortCircuiting.DataStructs

Methods

pretty :: CoalsTab -> Doc ann #

prettyList :: [CoalsTab] -> Doc ann #

type FreeVarSubsts = Map VName (TPrimExp Int64 VName) Source #

Free variable substitutions

type LmadRef = LMAD (TPrimExp Int64 VName) Source #

An LMAD specialized to TPrimExps (a typed primexp)

data MemRefs Source #

Constructors

MemRefs 

Fields

  • dstrefs :: AccessSummary

    The access summary of all references (reads and writes) to the destination of a coalescing entry

  • srcwrts :: AccessSummary

    The access summary of all writes to the source of a coalescing entry

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.

data BotUpEnv Source #

Constructors

BotUpEnv 

Fields

  • scals :: ScalarTab

    maps scalar variables to theirs PrimExp expansion

  • activeCoals :: CoalsTab

    Optimistic coalescing info. We are currently trying to coalesce these memory blocks.

  • successCoals :: CoalsTab

    Committed (successfull) coalescing info. These memory blocks have been successfully coalesced.

  • inhibit :: InhibitTab

    The coalescing failures from this pass. We will no longer try to merge these memory blocks.

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 #

Attempt to convert a VName to a PrimExp.

First look in ScalarTab to see if we have recorded the scalar value of the argument. Otherwise look up the type of the argument and return a LeafExp if it is a PrimType.

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.

getUniqueMemFParam :: [Param FParamMem] -> Map VName Space Source #

Get memory blocks in a list of FParam that are used for unique arrays in the same list of FParam.

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).