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

Language.Fortran.Analysis.SemanticTypes

Synopsis

Documentation

type Kind = Int Source #

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 defined by a single type, and a set of dimensions. Note that assumed-shape arrays which only "store" array rank cannot be represented.

TCustom String

Constructor to use for F77 structures, F90 DDTs

Instances

Instances details
Out SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

docPrec :: Int -> SemType -> Doc #

doc :: SemType -> Doc #

docList :: [SemType] -> Doc #

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

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

toConstr :: SemType -> Constr #

dataTypeOf :: SemType -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Associated Types

type Rep SemType :: Type -> Type #

Methods

from :: SemType -> Rep SemType x #

to :: Rep SemType x -> SemType #

Show SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Binary SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

put :: SemType -> Put #

get :: Get SemType #

putList :: [SemType] -> Put #

NFData SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

rnf :: SemType -> () #

Pretty SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Eq SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

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

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

Ord SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep SemType = D1 ('MetaData "SemType" "Language.Fortran.Analysis.SemanticTypes" "fortran-src-0.12.0-inplace" '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)))))

data Dimensions Source #

The declared dimensions of an array variable.

Each dimension is of the form (dim_lower, dim_upper).

Constructors

DimensionsCons !(Int, Int) Dimensions

Another dimension in the dimension list.

DimensionsEnd

No more dimensions.

DimensionsFinalStar

The final dimension is dynamic (represented by a star * in syntax). This indicates an assumed-size array.

Instances

Instances details
Out Dimensions Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Data Dimensions Source # 
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) -> Dimensions -> c Dimensions #

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

toConstr :: Dimensions -> Constr #

dataTypeOf :: Dimensions -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Dimensions Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Associated Types

type Rep Dimensions :: Type -> Type #

Show Dimensions Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Binary Dimensions Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

NFData Dimensions Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

rnf :: Dimensions -> () #

Eq Dimensions Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Ord Dimensions Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep Dimensions Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep Dimensions = D1 ('MetaData "Dimensions" "Language.Fortran.Analysis.SemanticTypes" "fortran-src-0.12.0-inplace" 'False) (C1 ('MetaCons "DimensionsCons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Int, Int)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dimensions)) :+: (C1 ('MetaCons "DimensionsEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DimensionsFinalStar" 'PrefixI 'False) (U1 :: Type -> Type)))

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

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

Will not return Just [].

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

Defined in Language.Fortran.Analysis.SemanticTypes

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

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

toConstr :: CharacterLen -> Constr #

dataTypeOf :: CharacterLen -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic CharacterLen Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Associated Types

type Rep CharacterLen :: Type -> Type #

Show CharacterLen Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Binary CharacterLen Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

NFData CharacterLen Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Methods

rnf :: CharacterLen -> () #

Eq CharacterLen Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Ord CharacterLen Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep CharacterLen Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

type Rep CharacterLen = D1 ('MetaData "CharacterLen" "Language.Fortran.Analysis.SemanticTypes" "fortran-src-0.12.0-inplace" '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))))

charLenToValue :: CharacterLen -> Maybe (Value a) Source #

Attempt to recover the Value that generated the given CharacterLen.

recoverSemTypeTypeSpec :: forall a. a -> SrcSpan -> FortranVersion -> SemType -> TypeSpec a Source #

Recover the most appropriate TypeSpec for the given SemType, depending on the given FortranVersion.

Kinds weren't formalized as a syntactic feature until Fortran 90, so we ask for a context. If possible (>=F90), we prefer the more explicit representation e.g. REAL(8). For older versions, for specific type-kind combinations, DOUBLE PRECISION and DOUBLE COMPLEX are used instead. However, we otherwise don't shy away from adding kind info regardless of theoretical version support.

Array types don't work properly, due to array type info being in a parent node that holds individual elements.

kindOfBaseType :: BaseType -> Int Source #

Given a BaseType infer the "default" kind (or size of the variable in memory).

Useful when you need a default kind, but gives you an unwrapped type. Consider using Analysis.deriveSemTypeFromBaseType also.

Further documentation: https://docs.oracle.com/cd/E19957-01/805-4939/c400041360f5/index.html