Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Futhark.Analysis.AccessPattern
Synopsis
- analyseDimAccesses :: Analyse rep => Prog rep -> IndexTable rep
- analyseFunction :: Analyse rep => FunDef rep -> IndexTable rep
- vnameFromSegOp :: SegOpName -> VName
- analysisPropagateByTransitivity :: IndexTable rep -> IndexTable rep
- isInvariant :: DimAccess rep -> Bool
- class Analyse rep
- type IndexTable rep = Map SegOpName (Map ArrayName (Map IndexExprName [DimAccess rep]))
- type ArrayName = (VName, [BodyType], [Int])
- data DimAccess rep = DimAccess {}
- type IndexExprName = VName
- data BodyType
- data SegOpName
- data Context rep = Context {
- assignments :: Map VName (VariableInfo rep)
- slices :: Map IndexExprName (ArrayName, [VName], [DimAccess rep])
- parents :: [BodyType]
- currentLevel :: Int
- analyseIndex :: Context rep -> [VName] -> VName -> [DimIndex SubExp] -> (Context rep, IndexTable rep)
- data VariableInfo rep = VariableInfo {
- deps :: Names
- level :: Int
- parents_nest :: [BodyType]
- variableType :: VarType
- data VarType
- isCounter :: VarType -> Bool
- data Dependency = Dependency {}
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.
vnameFromSegOp :: SegOpName -> VName Source #
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²
isInvariant :: DimAccess rep -> Bool Source #
A representation where we can analyse access patterns.
Minimal complete definition
analyseOp
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.
Collect all features of access to a specific dimension of an array.
Constructors
DimAccess | |
Fields
|
type IndexExprName = VName Source #
Name of an array indexing expression. Taken from the pattern of the expression.
Constructors
SegOpName SegOpName | |
LoopBodyName VName | |
CondBodyName VName |
Name of a SegOp, used to identify the SegOp that an array access is contained in.
Constructors
SegmentedMap VName | |
SegmentedRed VName | |
SegmentedScan VName | |
SegmentedHist VName |
Instances
Show SegOpName Source # | |
Eq SegOpName Source # | |
Ord SegOpName Source # | |
Pretty SegOpName Source # | |
Defined in Futhark.Analysis.AccessPattern | |
Pretty (IndexTable rep) Source # | |
Defined in Futhark.Analysis.AccessPattern |
Used during the analysis to keep track of the dependencies of patterns encountered so far.
Constructors
Context | |
Fields
|
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 | |
Fields
|
Instances
Show (VariableInfo rep) Source # | |
Defined in Futhark.Analysis.AccessPattern Methods showsPrec :: Int -> VariableInfo rep -> ShowS # show :: VariableInfo rep -> String # showList :: [VariableInfo rep] -> ShowS # | |
Eq (VariableInfo rep) Source # | |
Defined in Futhark.Analysis.AccessPattern Methods (==) :: VariableInfo rep -> VariableInfo rep -> Bool # (/=) :: VariableInfo rep -> VariableInfo rep -> Bool # |
data Dependency Source #
Tuple of patternName and nested level
it index occurred at, as well as
what the actual iteration type is.
Constructors
Dependency | |
Instances
Show Dependency Source # | |
Defined in Futhark.Analysis.AccessPattern Methods showsPrec :: Int -> Dependency -> ShowS # show :: Dependency -> String # showList :: [Dependency] -> ShowS # | |
Eq Dependency Source # | |
Defined in Futhark.Analysis.AccessPattern |