| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Camfort.Specification.Stencils.InferenceBackend
- type Span a = (a, a)
- mkTrivialSpan :: t -> (t, t)
- inferFromIndices :: VecList Int -> Specification
- inferFromIndicesWithoutLinearity :: VecList Int -> Specification
- simplify :: Result Spatial -> Result Spatial
- simplifySpatial :: Spatial -> Spatial
- reducor :: [a] -> ([a] -> [a]) -> ([a] -> Int) -> [a]
- fromRegionsToSpec :: IsNatural n => [Span (Vec n Int)] -> Result Spatial
- toSpecND :: Span (Vec n Int) -> Result Spatial
- toSpec1D :: Dimension -> Int -> Int -> Result Spatial
- normaliseSpan :: Span (Vec n Int) -> Span (Vec n Int)
- spanBoundingBox :: Span (Vec n Int) -> Span (Vec n Int) -> Span (Vec n Int)
- composeConsecutiveSpans :: Span (Vec n Int) -> Span (Vec n Int) -> [Span (Vec n Int)]
- inferMinimalVectorRegions :: Permutable n => [Vec n Int] -> [Span (Vec n Int)]
- allRegionPermutations :: Permutable n => [Span (Vec n Int)] -> [Span (Vec n Int)]
- foldL :: (a -> a -> [a]) -> [a] -> [a]
- minimaliseRegions :: [Span (Vec n Int)] -> [Span (Vec n Int)]
- containedWithin :: Span (Vec n Int) -> Span (Vec n Int) -> Bool
- class Permutable n where
- type family Selection n a where ...
- data VecList a where- VL :: (IsNatural n, Permutable n) => [Vec n a] -> VecList a
 
- data List a where- List :: (IsNatural n, Permutable n) => Vec n a -> List a
 
- lnil :: List a
- lcons :: a -> List a -> List a
- fromList :: [a] -> List a
- fromLists :: [[Int]] -> VecList Int
- data EqT a b where
Documentation
mkTrivialSpan :: t -> (t, t) Source #
simplifySpatial :: Spatial -> Spatial Source #
composeConsecutiveSpans :: Span (Vec n Int) -> Span (Vec n Int) -> [Span (Vec n Int)] Source #
Given two spans, if they are consecutive (i.e., (lower1, upper1) (lower2, upper2) where lower2 = upper1 + 1) then compose together returning Just of the new span. Otherwise Nothing
inferMinimalVectorRegions :: Permutable n => [Vec n Int] -> [Span (Vec n Int)] Source #
|inferMinimalVectorRegions| a key part of the algorithm, from a list of n-dimensional relative indices it infers a list of (possibly overlapping) 1-dimensional spans (vectors) within the n-dimensional space. Built from |minimalise| and |allRegionPermutations|
allRegionPermutations :: Permutable n => [Span (Vec n Int)] -> [Span (Vec n Int)] Source #
Map from a lists of n-dimensional spans of relative indices into all possible contiguous spans within the n-dimensional space (individual pass)
minimaliseRegions :: [Span (Vec n Int)] -> [Span (Vec n Int)] Source #
Collapses the regions into a small set by looking for potential overlaps and eliminating those that overlap
containedWithin :: Span (Vec n Int) -> Span (Vec n Int) -> Bool Source #
Binary predicate on whether the first region containedWithin the second
class Permutable n where Source #
Defines the (total) class of vector sizes which are permutable, along with
    the permutation function which pairs permutations with the unpermute
    operation 
Minimal complete definition
Methods
selectionsV :: Vec n a -> [Selection n a] Source #
permutationsV :: Vec n a -> [(Vec n a, Vec n a -> Vec n a)] Source #
Instances
| Permutable Z Source # | |
| Permutable (S Z) Source # | |
| Permutable (S n) => Permutable (S (S n)) Source # | |
Constructors
| VL :: (IsNatural n, Permutable n) => [Vec n a] -> VecList a |