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

Language.Fortran.Common.Array

Synopsis

Documentation

data Dim a Source #

A single array dimension with bounds of type a.

  • Num a => Dim a is a static, known-size dimension.
  • Dim (Expression ()) is a dimension with unevaluated bounds expressions. Note that these bounds may be constant expressions, or refer to dummy variables, or be invalid.
  • Num a => Dim (Maybe a) is a dimension where some bounds are known, and others are not. This may be useful to record some information about dynamic explicit-shape arrays.

Constructors

Dim 

Fields

Instances

Instances details
Foldable Dim Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

fold :: Monoid m => Dim m -> m #

foldMap :: Monoid m => (a -> m) -> Dim a -> m #

foldMap' :: Monoid m => (a -> m) -> Dim a -> m #

foldr :: (a -> b -> b) -> b -> Dim a -> b #

foldr' :: (a -> b -> b) -> b -> Dim a -> b #

foldl :: (b -> a -> b) -> b -> Dim a -> b #

foldl' :: (b -> a -> b) -> b -> Dim a -> b #

foldr1 :: (a -> a -> a) -> Dim a -> a #

foldl1 :: (a -> a -> a) -> Dim a -> a #

toList :: Dim a -> [a] #

null :: Dim a -> Bool #

length :: Dim a -> Int #

elem :: Eq a => a -> Dim a -> Bool #

maximum :: Ord a => Dim a -> a #

minimum :: Ord a => Dim a -> a #

sum :: Num a => Dim a -> a #

product :: Num a => Dim a -> a #

Traversable Dim Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

traverse :: Applicative f => (a -> f b) -> Dim a -> f (Dim b) #

sequenceA :: Applicative f => Dim (f a) -> f (Dim a) #

mapM :: Monad m => (a -> m b) -> Dim a -> m (Dim b) #

sequence :: Monad m => Dim (m a) -> m (Dim a) #

Functor Dim Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

Out a => Out (Dim a) Source #

Fortran syntax uses lower:upper, so only provide an Out instance for that style.

Instance details

Defined in Language.Fortran.Common.Array

Methods

docPrec :: Int -> Dim a -> Doc #

doc :: Dim a -> Doc #

docList :: [Dim a] -> Doc #

Data a => Data (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

toConstr :: Dim a -> Constr #

dataTypeOf :: Dim a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Associated Types

type Rep (Dim a) :: Type -> Type #

Methods

from :: Dim a -> Rep (Dim a) x #

to :: Rep (Dim a) x -> Dim a #

Show a => Show (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

show :: Dim a -> String #

showList :: [Dim a] -> ShowS #

Binary a => Binary (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

put :: Dim a -> Put #

get :: Get (Dim a) #

putList :: [Dim a] -> Put #

NFData a => NFData (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

rnf :: Dim a -> () #

Out (Dim a) => Pretty (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

pprint' :: FortranVersion -> Dim a -> Doc Source #

Eq a => Eq (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

Ord a => Ord (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

compare :: Dim a -> Dim a -> Ordering #

(<) :: Dim a -> Dim a -> Bool #

(<=) :: Dim a -> Dim a -> Bool #

(>) :: Dim a -> Dim a -> Bool #

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

max :: Dim a -> Dim a -> Dim a #

min :: Dim a -> Dim a -> Dim a #

type Rep (Dim a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

type Rep (Dim a) = D1 ('MetaData "Dim" "Language.Fortran.Common.Array" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "Dim" 'PrefixI 'True) (S1 ('MetaSel ('Just "dimLower") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "dimUpper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

data Dims t a Source #

Fortran array dimensions, defined by a list of Dims storing lower and upper bounds.

You select the list type t (which should be Functor, Foldable and Traversable) and the bound type a (e.g. Int).

Using a non-empty list type such as NonEmpty will disallow representing zero-dimension arrays, providing extra soundness.

Note the following excerpt from the F2018 standard (8.5.8.2 Explicit-shape array):

If the upper bound is less than the lower bound, the range is empty, the
extent in that dimension is zero, and the array is of zero size.

Note that the Foldable instance does not provide "dimension-like" access to this type. That is, length (a :: Dims t a) will _not_ tell you how many dimensions a represents. Use dimsLength for that.

Constructors

DimsExplicitShape

Explicit-shape array. All dimensions are known.

Fields

  • (t (Dim a))

    list of all dimensions

DimsAssumedSize

Assumed-size array. The final dimension has no upper bound (it is obtained from its effective argument). Earlier dimensions may be defined like explicit-shape arrays.

Fields

  • (Maybe (t (Dim a)))

    list of all dimensions except last

  • a

    lower bound of last dimension

DimsAssumedShape

Assumed-shape array. Shape is taken from effective argument. We store the lower bound for each dimension, and thus also the rank (via list length).

Fields

  • (t a)

    list of lower bounds

Instances

Instances details
Foldable t => Foldable (Dims t) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

fold :: Monoid m => Dims t m -> m #

foldMap :: Monoid m => (a -> m) -> Dims t a -> m #

foldMap' :: Monoid m => (a -> m) -> Dims t a -> m #

foldr :: (a -> b -> b) -> b -> Dims t a -> b #

foldr' :: (a -> b -> b) -> b -> Dims t a -> b #

foldl :: (b -> a -> b) -> b -> Dims t a -> b #

foldl' :: (b -> a -> b) -> b -> Dims t a -> b #

foldr1 :: (a -> a -> a) -> Dims t a -> a #

foldl1 :: (a -> a -> a) -> Dims t a -> a #

toList :: Dims t a -> [a] #

null :: Dims t a -> Bool #

length :: Dims t a -> Int #

elem :: Eq a => a -> Dims t a -> Bool #

maximum :: Ord a => Dims t a -> a #

minimum :: Ord a => Dims t a -> a #

sum :: Num a => Dims t a -> a #

product :: Num a => Dims t a -> a #

Traversable t => Traversable (Dims t) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

traverse :: Applicative f => (a -> f b) -> Dims t a -> f (Dims t b) #

sequenceA :: Applicative f => Dims t (f a) -> f (Dims t a) #

mapM :: Monad m => (a -> m b) -> Dims t a -> m (Dims t b) #

sequence :: Monad m => Dims t (m a) -> m (Dims t a) #

Functor t => Functor (Dims t) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

fmap :: (a -> b) -> Dims t a -> Dims t b #

(<$) :: a -> Dims t b -> Dims t a #

(Foldable t, Functor t, Out (Dim a), Out a) => Out (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

docPrec :: Int -> Dims t a -> Doc #

doc :: Dims t a -> Doc #

docList :: [Dims t a] -> Doc #

(Data a, Data (t a), Data (t (Dim a)), Typeable t) => Data (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

toConstr :: Dims t a -> Constr #

dataTypeOf :: Dims t a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Associated Types

type Rep (Dims t a) :: Type -> Type #

Methods

from :: Dims t a -> Rep (Dims t a) x #

to :: Rep (Dims t a) x -> Dims t a #

(Show a, Show (t a), Show (t (Dim a))) => Show (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

showsPrec :: Int -> Dims t a -> ShowS #

show :: Dims t a -> String #

showList :: [Dims t a] -> ShowS #

(Binary a, Binary (t a), Binary (t (Dim a))) => Binary (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

put :: Dims t a -> Put #

get :: Get (Dims t a) #

putList :: [Dims t a] -> Put #

(NFData a, NFData (t a), NFData (t (Dim a))) => NFData (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

rnf :: Dims t a -> () #

Out (Dims t a) => Pretty (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

pprint' :: FortranVersion -> Dims t a -> Doc Source #

(Eq a, Eq (t a), Eq (t (Dim a))) => Eq (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

Methods

(==) :: Dims t a -> Dims t a -> Bool #

(/=) :: Dims t a -> Dims t a -> Bool #

(Ord a, Ord (t a), Ord (t (Dim a))) => Ord (Dims t a) Source #

This instance is purely for convenience. No definition of ordering is provided, and the implementation may change at any time.

Instance details

Defined in Language.Fortran.Common.Array

Methods

compare :: Dims t a -> Dims t a -> Ordering #

(<) :: Dims t a -> Dims t a -> Bool #

(<=) :: Dims t a -> Dims t a -> Bool #

(>) :: Dims t a -> Dims t a -> Bool #

(>=) :: Dims t a -> Dims t a -> Bool #

max :: Dims t a -> Dims t a -> Dims t a #

min :: Dims t a -> Dims t a -> Dims t a #

type Rep (Dims t a) Source # 
Instance details

Defined in Language.Fortran.Common.Array

type Rep (Dims t a) = D1 ('MetaData "Dims" "Language.Fortran.Common.Array" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "DimsExplicitShape" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (t (Dim a)))) :+: (C1 ('MetaCons "DimsAssumedSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (t (Dim a)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "DimsAssumedShape" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (t a)))))

dimsTraverse :: (Traversable t, Applicative f) => Dims t (f a) -> f (Dims t a) Source #

Traverse over the functor in a Dims value with a functor bound type.

For example, to turn a Dims t (Maybe a) into a Maybe (Dims t a).

dimsLength :: Foldable t => Dims t a -> Int Source #

How many dimensions does the given Dims represent?