camfort-0.802: CamFort - Cambridge Fortran infrastructure

Safe HaskellNone
LanguageHaskell98

Camfort.Specification.Stencils.Syntax

Contents

Synopsis

Documentation

0. Representations

data Result a Source #

Constructors

Exact a 
Bound (Maybe a) (Maybe a) 

Instances

Functor Result Source # 

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Eq a => Eq (Result a) Source # 

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

Data a => Data (Result a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Result a -> c (Result a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Result a) #

toConstr :: Result a -> Constr #

dataTypeOf :: Result a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Result a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Result a)) #

gmapT :: (forall b. Data b => b -> b) -> Result a -> Result a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Result a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Result a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Result a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Result a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Result a -> m (Result a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Result a -> m (Result a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Result a -> m (Result a) #

Show a => Show (Result a) Source # 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Show (Result Spatial) Source # 
RegionRig (Result Spatial) Source # 
Model (Result Spatial) Source # 
type Domain (Result Spatial) Source # 

1 . Specification syntax

lookupAggregate :: Eq a => [([a], b)] -> a -> [b] Source #

data Specification Source #

Instances

Eq Specification Source # 
Data Specification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Specification -> c Specification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Specification #

toConstr :: Specification -> Constr #

dataTypeOf :: Specification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Specification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Specification) #

gmapT :: (forall b. Data b => b -> b) -> Specification -> Specification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Specification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Specification -> r #

gmapQ :: (forall d. Data d => d -> u) -> Specification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Specification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Specification -> m Specification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Specification -> m Specification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Specification -> m Specification #

Show Specification Source # 
Model Specification Source # 
SynToAst Spec Specification Source # 
SynToAst Specification (Either RegionEnv SpecDecls) Source # 
type Domain Specification Source # 

data Temporal Source #

Constructors

Dependency [String] Bool 

Instances

Eq Temporal Source # 
Data Temporal Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Temporal -> c Temporal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Temporal #

toConstr :: Temporal -> Constr #

dataTypeOf :: Temporal -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Temporal) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Temporal) #

gmapT :: (forall b. Data b => b -> b) -> Temporal -> Temporal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Temporal -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Temporal -> r #

gmapQ :: (forall d. Data d => d -> u) -> Temporal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Temporal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Temporal -> m Temporal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Temporal -> m Temporal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Temporal -> m Temporal #

Show Temporal Source # 

data Spatial Source #

Constructors

Spatial 

Instances

Eq Spatial Source # 

Methods

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

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

Data Spatial Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Spatial -> c Spatial #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Spatial #

toConstr :: Spatial -> Constr #

dataTypeOf :: Spatial -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Spatial) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Spatial) #

gmapT :: (forall b. Data b => b -> b) -> Spatial -> Spatial #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Spatial -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Spatial -> r #

gmapQ :: (forall d. Data d => d -> u) -> Spatial -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Spatial -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Spatial -> m Spatial #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Spatial -> m Spatial #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Spatial -> m Spatial #

Show Spatial Source # 
RegionRig Spatial Source # 
Model Spatial Source # 
Show (Result Spatial) Source # 
RegionRig (Result Spatial) Source # 
Model (Result Spatial) Source # 
type Domain Spatial Source # 
type Domain (Result Spatial) Source # 

hasDuplicates :: Eq a => [a] -> ([a], Bool) Source #

data Linearity Source #

Constructors

Linear 
NonLinear 

Instances

Eq Linearity Source # 
Data Linearity Source # 

Methods

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 :: (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 #

RegionRig Linearity Source # 
SynToAst [Mod] (Linearity, Maybe Mod) Source # 

type Depth = Int Source #

data Region where Source #

Instances

Eq Region Source # 

Methods

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

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

Data Region Source # 

Methods

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 :: (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 # 
Model Region Source # 
type Domain Region Source # 
type Domain Region = Set [Int]

newtype RegionProd Source #

Constructors

Product 

Fields

Instances

Eq RegionProd Source # 
Data RegionProd Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RegionProd -> c RegionProd #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RegionProd #

toConstr :: RegionProd -> Constr #

dataTypeOf :: RegionProd -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RegionProd) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RegionProd) #

gmapT :: (forall b. Data b => b -> b) -> RegionProd -> RegionProd #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RegionProd -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RegionProd -> r #

gmapQ :: (forall d. Data d => d -> u) -> RegionProd -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RegionProd -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RegionProd -> m RegionProd #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RegionProd -> m RegionProd #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RegionProd -> m RegionProd #

Ord RegionProd Source # 
Show RegionProd Source # 
PartialMonoid RegionProd Source # 
Model RegionProd Source # 
type Domain RegionProd Source # 

newtype RegionSum Source #

Constructors

Sum 

Fields

Instances

Eq RegionSum Source # 
Data RegionSum Source # 

Methods

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 :: (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 # 
RegionRig RegionSum Source # 
Model RegionSum Source # 
SynToAst Region RegionSum Source # 
SynToAst Specification (Either RegionEnv SpecDecls) Source # 
type Domain RegionSum Source # 

showL :: Show a => [a] -> String Source #

showRegion :: (Show a1, Show a) => [Char] -> a -> a1 -> Bool -> [Char] Source #

groupKeyBy :: Eq b => [(a, b)] -> [([a], b)] Source #