fortran-vars-0.4.0: Fortran memory model and other static analysis tools.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Fortran.Vars.Rep

Description

Definitions for representing Fortran values and types.

Synopsis

Types

data SemType Source #

Semantic type assigned to variables.

BaseType stores the "type tag" given in syntax. SemTypes add metadata (kind and length), and resolve some "simple" types to a core type with a preset kind (e.g. `DOUBLE PRECISION` -> `REAL(8)`).

Fortran 90 (and beyond) features may not be well supported.

Constructors

TInteger Kind 
TReal Kind 
TComplex Kind 
TLogical Kind 
TByte Kind 
TCharacter CharacterLen Kind 
TArray SemType Dimensions

A Fortran array type is represented by a type and a set of dimensions.

TCustom String

Constructor to use for F77 structures, F90 DDTs

Instances

Instances details
Out SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

FromJSON SemType Source # 
Instance details

Defined in Language.Fortran.Vars.Orphans

ToJSON SemType Source # 
Instance details

Defined in Language.Fortran.Vars.Orphans

Data SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

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

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

toConstr :: SemType -> Constr Source #

dataTypeOf :: SemType -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Associated Types

type Rep SemType :: Type -> Type Source #

Show SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Binary SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

NFData SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

rnf :: SemType -> () Source #

Pretty SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Eq SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Ord SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep SemType 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep SemType = D1 ('MetaData "SemType" "Language.Fortran.Analysis.SemanticTypes" "fortran-src-0.15.0-c374304f6a26b2e6e1e1e09dd9acee640e5193a35a08d212d6794a128ceb6d72" 'False) (((C1 ('MetaCons "TInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TReal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind))) :+: (C1 ('MetaCons "TComplex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TLogical" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)))) :+: ((C1 ('MetaCons "TByte" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CharacterLen) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind))) :+: (C1 ('MetaCons "TArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SemType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dimensions)) :+: C1 ('MetaCons "TCustom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

type Kind = Int Source #

data CharacterLen Source #

Constructors

CharLenStar

specified with a *

CharLenColon

specified with a : (Fortran2003) FIXME, possibly, with a more robust const-exp:

CharLenExp

specified with a non-trivial expression

CharLenInt Int

specified with a constant integer

Instances

Instances details
Out CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

FromJSON CharacterLen Source # 
Instance details

Defined in Language.Fortran.Vars.Orphans

ToJSON CharacterLen Source # 
Instance details

Defined in Language.Fortran.Vars.Orphans

Data CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

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

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

toConstr :: CharacterLen -> Constr Source #

dataTypeOf :: CharacterLen -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Associated Types

type Rep CharacterLen :: Type -> Type Source #

Show CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Binary CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

NFData CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

rnf :: CharacterLen -> () Source #

Eq CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Ord CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep CharacterLen 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep CharacterLen = D1 ('MetaData "CharacterLen" "Language.Fortran.Analysis.SemanticTypes" "fortran-src-0.15.0-c374304f6a26b2e6e1e1e09dd9acee640e5193a35a08d212d6794a128ceb6d72" 'False) ((C1 ('MetaCons "CharLenStar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CharLenColon" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CharLenExp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CharLenInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

type Dimensions = Dims NonEmpty (Maybe Int) Source #

The main dimension type is a non-empty list of dimensions where each bound is Maybe Int. Nothing bounds indicate a dynamic bound (e.g. uses a dummy variable).

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 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

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

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

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

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

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

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

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

toList :: Dim a -> [a] Source #

null :: Dim a -> Bool Source #

length :: Dim a -> Int Source #

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

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

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

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

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

Traversable Dim 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

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

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

Functor Dim 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

Out a => Out (Dim a)

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 Source #

doc :: Dim a -> Doc Source #

docList :: [Dim a] -> Doc Source #

FromJSON (Dim (Maybe Int)) Source # 
Instance details

Defined in Language.Fortran.Vars.Orphans

Data a => Data (Dim a) 
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) Source #

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

toConstr :: Dim a -> Constr Source #

dataTypeOf :: Dim a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic (Dim a) 
Instance details

Defined in Language.Fortran.Common.Array

Associated Types

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

Methods

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

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

Show a => Show (Dim a) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

show :: Dim a -> String Source #

showList :: [Dim a] -> ShowS Source #

Binary a => Binary (Dim a) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

put :: Dim a -> Put Source #

get :: Get (Dim a) Source #

putList :: [Dim a] -> Put Source #

NFData a => NFData (Dim a) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

rnf :: Dim a -> () Source #

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

Defined in Language.Fortran.Common.Array

Methods

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

Eq a => Eq (Dim a) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

Ord a => Ord (Dim a) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

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

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

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

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

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

type Rep (Dim a) 
Instance details

Defined in Language.Fortran.Common.Array

type Rep (Dim a) = D1 ('MetaData "Dim" "Language.Fortran.Common.Array" "fortran-src-0.15.0-c374304f6a26b2e6e1e1e09dd9acee640e5193a35a08d212d6794a128ceb6d72" '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 :: Type -> TYPE LiftedRep) 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
FromJSON Dimensions Source # 
Instance details

Defined in Language.Fortran.Vars.Orphans

Foldable t => Foldable (Dims t) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

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

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

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

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

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

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

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

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

null :: Dims t a -> Bool Source #

length :: Dims t a -> Int Source #

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

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

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

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

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

Traversable t => Traversable (Dims t) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

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

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

Functor t => Functor (Dims t) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

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

Defined in Language.Fortran.Common.Array

Methods

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

doc :: Dims t a -> Doc Source #

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

(Data a, Data (t a), Data (t (Dim a)), Typeable t) => Data (Dims t a) 
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) Source #

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

toConstr :: Dims t a -> Constr Source #

dataTypeOf :: Dims t a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic (Dims t a) 
Instance details

Defined in Language.Fortran.Common.Array

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.Common.Array

Methods

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

show :: Dims t a -> String Source #

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

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

Defined in Language.Fortran.Common.Array

Methods

put :: Dims t a -> Put Source #

get :: Get (Dims t a) Source #

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

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

Defined in Language.Fortran.Common.Array

Methods

rnf :: Dims t a -> () Source #

Out (Dims t a) => Pretty (Dims t a) 
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) 
Instance details

Defined in Language.Fortran.Common.Array

Methods

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

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

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

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 Source #

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

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

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

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

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

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

type Rep (Dims t a) 
Instance details

Defined in Language.Fortran.Common.Array

type Rep (Dims t a) = D1 ('MetaData "Dims" "Language.Fortran.Common.Array" "fortran-src-0.15.0-c374304f6a26b2e6e1e1e09dd9acee640e5193a35a08d212d6794a128ceb6d72" '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)))))

Compatibility

dimensionsToTuples :: Dimensions -> Maybe [(Int, Int)] Source #

Convert Dimensions data type to its previous type synonym (Maybe [(Int, Int)]).

Drops all information for array dimensions that aren't fully static/known.

Values

data ExpVal Source #

The evaluated value of a FORTRAN expression.

Instances

Instances details
FromJSON ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep

ToJSON ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep

Data ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep

Methods

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

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

toConstr :: ExpVal -> Constr Source #

dataTypeOf :: ExpVal -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep

Associated Types

type Rep ExpVal :: Type -> Type Source #

Show ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep

NFData ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep

Methods

rnf :: ExpVal -> () Source #

Eq ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep

Ord ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep

type Rep ExpVal Source # 
Instance details

Defined in Language.Fortran.Vars.Rep