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

Futhark.Analysis.AccessPattern

Synopsis

Documentation

analyseDimAccesses :: Analyse rep => Prog rep -> IndexTable rep Source #

Analyse each entry and accumulate the results.

analyseFunction :: Analyse rep => FunDef rep -> IndexTable rep Source #

Analyse each statement in a function body.

analysisPropagateByTransitivity :: IndexTable rep -> IndexTable rep Source #

Make segops on arrays transitive, ie. if > let A = segmap (..) xs -- A indexes into xs > let B = segmap (..) A -- B indexes into A Then B also derives all A's array-accesses, like xs. Runs in n²

class Analyse rep Source #

A representation where we can analyse access patterns.

Minimal complete definition

analyseOp

Instances

Instances details
Analyse GPU Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Analyse GPUMem Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Analyse MC Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

analyseOp :: Op MC -> Context MC -> [VName] -> (Context MC, IndexTable MC)

Analyse MCMem Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Analyse SOACS Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Analyse Seq Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Analyse SeqMem Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

type IndexTable rep = Map SegOpName (Map ArrayName (Map IndexExprName [DimAccess rep])) Source #

For each array access in a program, this data structure stores the dependencies of each dimension in the access, the array name, and the name of the SegOp that the access is contained in. Each DimAccess element corresponds to an access to a given dimension in the given array, in the same order of the dimensions.

type ArrayName = (VName, [BodyType], [Int]) Source #

Stores the name of an array, the nest of loops, kernels, conditionals in which it is constructed, and the existing layout of the array. The latter is currently largely unused and not trustworthy, but might be useful in the future.

data DimAccess rep Source #

Collect all features of access to a specific dimension of an array.

Constructors

DimAccess 

Fields

Instances

Instances details
Monoid (DimAccess rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

mempty :: DimAccess rep #

mappend :: DimAccess rep -> DimAccess rep -> DimAccess rep #

mconcat :: [DimAccess rep] -> DimAccess rep #

Semigroup (DimAccess rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

(<>) :: DimAccess rep -> DimAccess rep -> DimAccess rep #

sconcat :: NonEmpty (DimAccess rep) -> DimAccess rep #

stimes :: Integral b => b -> DimAccess rep -> DimAccess rep #

Show (DimAccess rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

showsPrec :: Int -> DimAccess rep -> ShowS #

show :: DimAccess rep -> String #

showList :: [DimAccess rep] -> ShowS #

Eq (DimAccess rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

(==) :: DimAccess rep -> DimAccess rep -> Bool #

(/=) :: DimAccess rep -> DimAccess rep -> Bool #

Pretty (DimAccess rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

pretty :: DimAccess rep -> Doc ann #

prettyList :: [DimAccess rep] -> Doc ann #

Pretty (IndexTable rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

pretty :: IndexTable rep -> Doc ann #

prettyList :: [IndexTable rep] -> Doc ann #

type IndexExprName = VName Source #

Name of an array indexing expression. Taken from the pattern of the expression.

data BodyType Source #

Instances

Instances details
Show BodyType Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Eq BodyType Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Ord BodyType Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Pretty BodyType Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

pretty :: BodyType -> Doc ann #

prettyList :: [BodyType] -> Doc ann #

Pretty (IndexTable rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

pretty :: IndexTable rep -> Doc ann #

prettyList :: [IndexTable rep] -> Doc ann #

data SegOpName Source #

Name of a SegOp, used to identify the SegOp that an array access is contained in.

Instances

Instances details
Show SegOpName Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Eq SegOpName Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Ord SegOpName Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Pretty SegOpName Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

pretty :: SegOpName -> Doc ann #

prettyList :: [SegOpName] -> Doc ann #

Pretty (IndexTable rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

pretty :: IndexTable rep -> Doc ann #

prettyList :: [IndexTable rep] -> Doc ann #

data Context rep Source #

Used during the analysis to keep track of the dependencies of patterns encountered so far.

Constructors

Context 

Fields

Instances

Instances details
Monoid (Context rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

mempty :: Context rep #

mappend :: Context rep -> Context rep -> Context rep #

mconcat :: [Context rep] -> Context rep #

Semigroup (Context rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

(<>) :: Context rep -> Context rep -> Context rep #

sconcat :: NonEmpty (Context rep) -> Context rep #

stimes :: Integral b => b -> Context rep -> Context rep #

Show (Context rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

showsPrec :: Int -> Context rep -> ShowS #

show :: Context rep -> String #

showList :: [Context rep] -> ShowS #

Eq (Context rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

(==) :: Context rep -> Context rep -> Bool #

(/=) :: Context rep -> Context rep -> Bool #

analyseIndex :: Context rep -> [VName] -> VName -> [DimIndex SubExp] -> (Context rep, IndexTable rep) Source #

Gets the dependencies of each dimension and either returns a result, or adds a slice to the context.

data VariableInfo rep Source #

Context Value (VariableInfo) is the type used in the context to categorize assignments. For example, a pattern might depend on a function parameter, a gtid, or some other pattern.

Constructors

VariableInfo 

Instances

Instances details
Show (VariableInfo rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Eq (VariableInfo rep) Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

(==) :: VariableInfo rep -> VariableInfo rep -> Bool #

(/=) :: VariableInfo rep -> VariableInfo rep -> Bool #

data VarType Source #

Instances

Instances details
Show VarType Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Eq VarType Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

(==) :: VarType -> VarType -> Bool #

(/=) :: VarType -> VarType -> Bool #

Pretty VarType Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Methods

pretty :: VarType -> Doc ann #

prettyList :: [VarType] -> Doc ann #

data Dependency Source #

Tuple of patternName and nested level it index occurred at, as well as what the actual iteration type is.

Constructors

Dependency 

Fields

Instances

Instances details
Show Dependency Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern

Eq Dependency Source # 
Instance details

Defined in Futhark.Analysis.AccessPattern