fortran-src-0.15.0: Parsers and analyses for Fortran standards 66, 77, 90, 95 and 2003 (partial).
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Fortran.Repr.Type.Array

Synopsis

Documentation

data FArrayType Source #

A Fortran array type.

An array type is defined by a scalar type together with a shape.

Constructors

FArrayType 

Instances

Instances details
Data FArrayType Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Methods

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

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

toConstr :: FArrayType -> Constr #

dataTypeOf :: FArrayType -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic FArrayType Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Associated Types

type Rep FArrayType :: Type -> Type #

Show FArrayType Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Eq FArrayType Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Ord FArrayType Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

type Rep FArrayType Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

type Rep FArrayType = D1 ('MetaData "FArrayType" "Language.Fortran.Repr.Type.Array" "fortran-src-0.15.0-inplace" 'False) (C1 ('MetaCons "FArrayType" 'PrefixI 'True) (S1 ('MetaSel ('Just "fatScalar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FScalarType) :*: S1 ('MetaSel ('Just "fatShape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Shape)))

newtype Shape Source #

The shape of a Fortran array is a list of extents. (The rank of the array is length of the list.)

Note that the F90 standard limits maximum array rank to 7 (R512).

TODO * An empty list here feels nonsensical. Perhaps this should be NonEmpty. * List type is inefficient here, since we don't care about pushing/popping, and list length is important. Use a vector type instead.

Constructors

Shape 

Fields

Instances

Instances details
Data Shape Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Methods

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

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

toConstr :: Shape -> Constr #

dataTypeOf :: Shape -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Shape Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Associated Types

type Rep Shape :: Type -> Type #

Methods

from :: Shape -> Rep Shape x #

to :: Rep Shape x -> Shape #

Show Shape Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Methods

showsPrec :: Int -> Shape -> ShowS #

show :: Shape -> String #

showList :: [Shape] -> ShowS #

Eq Shape Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Methods

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

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

Ord Shape Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

Methods

compare :: Shape -> Shape -> Ordering #

(<) :: Shape -> Shape -> Bool #

(<=) :: Shape -> Shape -> Bool #

(>) :: Shape -> Shape -> Bool #

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

max :: Shape -> Shape -> Shape #

min :: Shape -> Shape -> Shape #

type Rep Shape Source # 
Instance details

Defined in Language.Fortran.Repr.Type.Array

type Rep Shape = D1 ('MetaData "Shape" "Language.Fortran.Repr.Type.Array" "fortran-src-0.15.0-inplace" 'True) (C1 ('MetaCons "Shape" 'PrefixI 'True) (S1 ('MetaSel ('Just "getShape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Natural])))