Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Linearity
- data Region where
- type RegionDecl = (Variable, RegionSum)
- type RegionEnv = [(Variable, RegionSum)]
- newtype RegionProd = Product {}
- newtype RegionSum = Sum {
- unSum :: [RegionProd]
- data Spatial = Spatial RegionSum
- type SpecDecl = ([Variable], Specification)
- type SpecDecls = [SpecDecl]
- data Specification = Specification (Multiplicity (Approximation Spatial)) IsStencil
- type IsStencil = Bool
- type Variable = String
- absoluteRep :: Int
- fromBool :: Bool -> Linearity
- groupKeyBy :: Eq b => [(a, b)] -> [([a], b)]
- hasDuplicates :: Eq a => [a] -> ([a], Bool)
- isEmpty :: Specification -> Bool
- isUnit :: RegionRig t => t -> Bool
- pprintSpecDecls :: SpecDecls -> String
- setLinearity :: Linearity -> Specification -> Specification
Datatypes and Aliases
Instances
Eq Linearity Source # | |
Data Linearity Source # | |
Defined in Camfort.Specification.Stencils.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Linearity -> c Linearity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Linearity # toConstr :: Linearity -> Constr # dataTypeOf :: Linearity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Linearity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Linearity) # gmapT :: (forall b. Data b => b -> b) -> Linearity -> Linearity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Linearity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Linearity -> r # gmapQ :: (forall d. Data d => d -> u) -> Linearity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Linearity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Linearity -> m Linearity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Linearity -> m Linearity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Linearity -> m Linearity # |
Forward :: Depth -> Dimension -> IsRefl -> Region | |
Backward :: Depth -> Dimension -> IsRefl -> Region | |
Centered :: Depth -> Dimension -> IsRefl -> Region |
Instances
Eq Region Source # | |
Data Region Source # | |
Defined in Camfort.Specification.Stencils.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Region -> c Region # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Region # toConstr :: Region -> Constr # dataTypeOf :: Region -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Region) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region) # gmapT :: (forall b. Data b => b -> b) -> Region -> Region # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQ :: (forall d. Data d => d -> u) -> Region -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # | |
Ord Region Source # | |
Show Region Source # | |
type RegionDecl = (Variable, RegionSum) Source #
newtype RegionProd Source #
Instances
Sum | |
|
Instances
Eq RegionSum Source # | |
Data RegionSum Source # | |
Defined in Camfort.Specification.Stencils.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RegionSum -> c RegionSum # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RegionSum # toConstr :: RegionSum -> Constr # dataTypeOf :: RegionSum -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RegionSum) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RegionSum) # gmapT :: (forall b. Data b => b -> b) -> RegionSum -> RegionSum # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RegionSum -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RegionSum -> r # gmapQ :: (forall d. Data d => d -> u) -> RegionSum -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RegionSum -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RegionSum -> m RegionSum # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RegionSum -> m RegionSum # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RegionSum -> m RegionSum # | |
Show RegionSum Source # | |
SynToAst Region RegionSum Source # | |
Defined in Camfort.Specification.Stencils.CheckBackend | |
SynToAst Specification (Either RegionDecl SpecDecl) Source # | |
SynToAst (Maybe Region) (Maybe RegionSum) Source # | |
Defined in Camfort.Specification.Stencils.CheckBackend |
Instances
type SpecDecl = ([Variable], Specification) Source #
data Specification Source #
Instances
type IsStencil = Bool Source #
isStencil
is used to mark whether a specification is associated
| with a stencil computation, or a general array computation
Functions
absoluteRep :: Int Source #
groupKeyBy :: Eq b => [(a, b)] -> [([a], b)] Source #
hasDuplicates :: Eq a => [a] -> ([a], Bool) Source #
isEmpty :: Specification -> Bool Source #
pprintSpecDecls :: SpecDecls -> String Source #
setLinearity :: Linearity -> Specification -> Specification Source #