fortran-src-0.4.2: Parsers and analyses for Fortran standards 66, 77, 90 and 95.
Safe HaskellNone
LanguageHaskell2010

Language.Fortran.AST

Documentation

type A0 = () Source #

data AList t a Source #

Constructors

AList a SrcSpan [t a] 

Instances

Instances details
Functor t => Functor (AList t) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated (AList t) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: AList t a -> a Source #

setAnnotation :: a -> AList t a -> AList t a Source #

modifyAnnotation :: (a -> a) -> AList t a -> AList t a Source #

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: AList t a -> Constr #

dataTypeOf :: AList t a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: AList t a -> String #

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

Generic (AList t a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: AList t a -> () #

(Out a, Out (t a)) => Out (AList t a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> AList t a -> Doc

doc :: AList t a -> Doc

docList :: [AList t a] -> Doc

Spanned (AList t a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getSpan :: AList t a -> SrcSpan Source #

setSpan :: SrcSpan -> AList t a -> AList t a Source #

Pretty (e a) => Pretty (AList e a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Methods

pprint' :: FortranVersion -> AList e a -> Doc Source #

FirstParameter (AList t a) a Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getFirstParameter :: AList t a -> a Source #

setFirstParameter :: a -> AList t a -> AList t a Source #

SecondParameter (AList t a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (AList t a) Source # 
Instance details

Defined in Language.Fortran.AST

fromList :: Spanned (t a) => a -> [t a] -> AList t a Source #

fromList' :: Spanned (t a) => a -> [t a] -> Maybe (AList t a) Source #

fromReverseList :: Spanned (t ()) => [t ()] -> AList t () Source #

fromReverseList' :: Spanned (t ()) => [t ()] -> Maybe (AList t ()) Source #

aCons :: t a -> AList t a -> AList t a infixr 5 Source #

aReverse :: AList t a -> AList t a Source #

aStrip :: AList t a -> [t a] Source #

aStrip' :: Maybe (AList t a) -> [t a] Source #

aMap :: (t a -> r a) -> AList t a -> AList r a Source #

data BaseType Source #

Instances

Instances details
Eq BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Data BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: BaseType -> Constr #

dataTypeOf :: BaseType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Show BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Generic BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep BaseType :: Type -> Type #

Methods

from :: BaseType -> Rep BaseType x #

to :: Rep BaseType x -> BaseType #

Binary BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Methods

put :: BaseType -> Put #

get :: Get BaseType #

putList :: [BaseType] -> Put #

NFData BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: BaseType -> () #

Out BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> BaseType -> Doc

doc :: BaseType -> Doc

docList :: [BaseType] -> Doc

Pretty BaseType Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

type Rep BaseType Source # 
Instance details

Defined in Language.Fortran.AST

type Rep BaseType = D1 ('MetaData "BaseType" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (((C1 ('MetaCons "TypeInteger" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeReal" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeDoublePrecision" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeComplex" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeDoubleComplex" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TypeLogical" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeCharacter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CharacterLen)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :+: C1 ('MetaCons "TypeCustom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: (C1 ('MetaCons "ClassStar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ClassCustom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "TypeByte" 'PrefixI 'False) (U1 :: Type -> Type)))))

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

Defined in Language.Fortran.AST

Data CharacterLen Source # 
Instance details

Defined in Language.Fortran.AST

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 #

Ord CharacterLen Source # 
Instance details

Defined in Language.Fortran.AST

Show CharacterLen Source # 
Instance details

Defined in Language.Fortran.AST

Generic CharacterLen Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep CharacterLen :: Type -> Type #

Binary CharacterLen Source # 
Instance details

Defined in Language.Fortran.AST

NFData CharacterLen Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: CharacterLen -> () #

Out CharacterLen Source # 
Instance details

Defined in Language.Fortran.AST

Pretty CharacterLen Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

type Rep CharacterLen Source # 
Instance details

Defined in Language.Fortran.AST

type Rep CharacterLen = D1 ('MetaData "CharacterLen" "Language.Fortran.AST" "fortran-src-0.4.2-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))))

data TypeSpec a Source #

Constructors

TypeSpec a SrcSpan BaseType (Maybe (Selector a)) 

Instances

Instances details
Functor TypeSpec Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated TypeSpec Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: TypeSpec a -> Constr #

dataTypeOf :: TypeSpec a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: TypeSpec a -> String #

showList :: [TypeSpec a] -> ShowS #

Generic (TypeSpec a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: TypeSpec a -> () #

Out a => Out (TypeSpec a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> TypeSpec a -> Doc

doc :: TypeSpec a -> Doc

docList :: [TypeSpec a] -> Doc

Spanned (TypeSpec a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (TypeSpec a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (TypeSpec a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (TypeSpec a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (TypeSpec a) Source # 
Instance details

Defined in Language.Fortran.AST

data Selector a Source #

Constructors

Selector a SrcSpan (Maybe (Expression a)) (Maybe (Expression a)) 

Instances

Instances details
Functor Selector Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated Selector Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Selector a -> Constr #

dataTypeOf :: Selector a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Selector a -> String #

showList :: [Selector a] -> ShowS #

Generic (Selector a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Selector a -> () #

Out a => Out (Selector a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Selector a -> Doc

doc :: Selector a -> Doc

docList :: [Selector a] -> Doc

Spanned (Selector a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Selector a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Selector a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Selector a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Selector a) Source # 
Instance details

Defined in Language.Fortran.AST

data MetaInfo Source #

Constructors

MetaInfo 

Instances

Instances details
Eq MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

Data MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: MetaInfo -> Constr #

dataTypeOf :: MetaInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

Generic MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep MetaInfo :: Type -> Type #

Methods

from :: MetaInfo -> Rep MetaInfo x #

to :: Rep MetaInfo x -> MetaInfo #

NFData MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: MetaInfo -> () #

Out MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> MetaInfo -> Doc

doc :: MetaInfo -> Doc

docList :: [MetaInfo] -> Doc

type Rep MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

type Rep MetaInfo = D1 ('MetaData "MetaInfo" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (C1 ('MetaCons "MetaInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "miVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FortranVersion) :*: S1 ('MetaSel ('Just "miFilename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data ProgramFile a Source #

Constructors

ProgramFile MetaInfo [ProgramUnit a] 

Instances

Instances details
Functor ProgramFile Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ProgramFile a -> Constr #

dataTypeOf :: ProgramFile a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (ProgramFile a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: ProgramFile a -> () #

Out a => Out (ProgramFile a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> ProgramFile a -> Doc

doc :: ProgramFile a -> Doc

docList :: [ProgramFile a] -> Doc

Spanned (ProgramFile a) Source # 
Instance details

Defined in Language.Fortran.AST

IndentablePretty (ProgramFile a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

type Rep (ProgramFile a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ProgramFile a) = D1 ('MetaData "ProgramFile" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (C1 ('MetaCons "ProgramFile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MetaInfo) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ProgramUnit a])))

data ProgramUnit a Source #

Instances

Instances details
Functor ProgramUnit Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated ProgramUnit Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ProgramUnit a -> Constr #

dataTypeOf :: ProgramUnit a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: ProgramUnit a -> () #

Out a => Out (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> ProgramUnit a -> Doc

doc :: ProgramUnit a -> Doc

docList :: [ProgramUnit a] -> Doc

Spanned (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.AST

Named (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.AST

IndentablePretty [ProgramUnit a] Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (ProgramUnit a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (ProgramUnit a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ProgramUnit a) = D1 ('MetaData "ProgramUnit" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) ((C1 ('MetaCons "PUMain" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [ProgramUnit a]))))) :+: (C1 ('MetaCons "PUModule" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [ProgramUnit a]))))) :+: C1 ('MetaCons "PUSubroutine" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PrefixSuffix a)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [ProgramUnit a]))))))) :+: (C1 ('MetaCons "PUFunction" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TypeSpec a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PrefixSuffix a)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [ProgramUnit a])))))) :+: (C1 ('MetaCons "PUBlockData" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a]))) :+: C1 ('MetaCons "PUComment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment a)))))))

data Prefix a Source #

Instances

Instances details
Functor Prefix Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Prefix a -> Constr #

dataTypeOf :: Prefix a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Prefix a -> String #

showList :: [Prefix a] -> ShowS #

Generic (Prefix a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Prefix a -> () #

Out a => Out (Prefix a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Prefix a -> Doc

doc :: Prefix a -> Doc

docList :: [Prefix a] -> Doc

Spanned (Prefix a) Source # 
Instance details

Defined in Language.Fortran.AST

FirstParameter (Prefix a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Prefix a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Prefix a) Source # 
Instance details

Defined in Language.Fortran.AST

data Suffix a Source #

Constructors

SfxBind a SrcSpan (Maybe (Expression a)) 

Instances

Instances details
Functor Suffix Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Suffix a -> Constr #

dataTypeOf :: Suffix a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Suffix a -> String #

showList :: [Suffix a] -> ShowS #

Generic (Suffix a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Suffix a -> () #

Out a => Out (Suffix a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Suffix a -> Doc

doc :: Suffix a -> Doc

docList :: [Suffix a] -> Doc

Spanned (Suffix a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Suffix a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Suffix a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Suffix a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Suffix a) Source # 
Instance details

Defined in Language.Fortran.AST

newtype Comment a Source #

Constructors

Comment String 

Instances

Instances details
Functor Comment Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Eq (Comment a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Comment a -> Constr #

dataTypeOf :: Comment a -> DataType #

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

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

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

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

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

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

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

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

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

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

Show (Comment a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

show :: Comment a -> String #

showList :: [Comment a] -> ShowS #

Generic (Comment a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Comment a -> () #

Out a => Out (Comment a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Comment a -> Doc

doc :: Comment a -> Doc

docList :: [Comment a] -> Doc

type Rep (Comment a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Comment a) = D1 ('MetaData "Comment" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'True) (C1 ('MetaCons "Comment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Block a Source #

Instances

Instances details
Functor Block Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Conditioned Block Source # 
Instance details

Defined in Language.Fortran.AST

Labeled Block Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Block Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: Block a -> a Source #

setAnnotation :: a -> Block a -> Block a Source #

modifyAnnotation :: (a -> a) -> Block a -> Block a Source #

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Block a -> Constr #

dataTypeOf :: Block a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Block a -> String #

showList :: [Block a] -> ShowS #

Generic (Block a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Block a -> () #

Out a => Out (Block a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Block a -> Doc

doc :: Block a -> Doc

docList :: [Block a] -> Doc

Spanned (Block a) Source # 
Instance details

Defined in Language.Fortran.AST

IndentablePretty [Block a] Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty (Block a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Block a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Block a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Block a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Block a) = D1 ('MetaData "Block" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (((C1 ('MetaCons "BlStatement" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Statement a)))) :+: C1 ('MetaCons "BlForall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ForallHeader a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))))) :+: (C1 ('MetaCons "BlIf" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe (Expression a)])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[Block a]]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))) :+: C1 ('MetaCons "BlCase" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe (AList Index a)])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[Block a]]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))))) :+: ((C1 ('MetaCons "BlDo" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (DoSpecification a)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))) :+: C1 ('MetaCons "BlDoWhile" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))))) :+: (C1 ('MetaCons "BlInterface" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ProgramUnit a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Block a])))) :+: C1 ('MetaCons "BlComment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Comment a)))))))

data Statement a Source #

Constructors

StDeclaration a SrcSpan (TypeSpec a) (Maybe (AList Attribute a)) (AList Declarator a) 
StStructure a SrcSpan (Maybe String) (AList StructureItem a) 
StIntent a SrcSpan Intent (AList Expression a) 
StOptional a SrcSpan (AList Expression a) 
StPublic a SrcSpan (Maybe (AList Expression a)) 
StPrivate a SrcSpan (Maybe (AList Expression a)) 
StProtected a SrcSpan (Maybe (AList Expression a)) 
StSave a SrcSpan (Maybe (AList Expression a)) 
StDimension a SrcSpan (AList Declarator a) 
StAllocatable a SrcSpan (AList Declarator a) 
StAsynchronous a SrcSpan (AList Declarator a) 
StPointer a SrcSpan (AList Declarator a) 
StTarget a SrcSpan (AList Declarator a) 
StValue a SrcSpan (AList Declarator a) 
StVolatile a SrcSpan (AList Declarator a) 
StData a SrcSpan (AList DataGroup a) 
StAutomatic a SrcSpan (AList Declarator a) 
StNamelist a SrcSpan (AList Namelist a) 
StParameter a SrcSpan (AList Declarator a) 
StExternal a SrcSpan (AList Expression a) 
StIntrinsic a SrcSpan (AList Expression a) 
StCommon a SrcSpan (AList CommonGroup a) 
StEquivalence a SrcSpan (AList (AList Expression) a) 
StFormat a SrcSpan (AList FormatItem a) 
StImplicit a SrcSpan (Maybe (AList ImpList a)) 
StEntry a SrcSpan (Expression a) (Maybe (AList Expression a)) (Maybe (Expression a)) 
StInclude a SrcSpan (Expression a) (Maybe [Block a]) 
StDo a SrcSpan (Maybe String) (Maybe (Expression a)) (Maybe (DoSpecification a)) 
StDoWhile a SrcSpan (Maybe String) (Maybe (Expression a)) (Expression a) 
StEnddo a SrcSpan (Maybe String) 
StCycle a SrcSpan (Maybe (Expression a)) 
StExit a SrcSpan (Maybe (Expression a)) 
StIfLogical a SrcSpan (Expression a) (Statement a) 
StIfArithmetic a SrcSpan (Expression a) (Expression a) (Expression a) (Expression a) 
StIfThen a SrcSpan (Maybe String) (Expression a) 
StElse a SrcSpan (Maybe String) 
StElsif a SrcSpan (Maybe String) (Expression a) 
StEndif a SrcSpan (Maybe String) 
StSelectCase a SrcSpan (Maybe String) (Expression a) 
StCase a SrcSpan (Maybe String) (Maybe (AList Index a)) 
StEndcase a SrcSpan (Maybe String) 
StFunction a SrcSpan (Expression a) (AList Expression a) (Expression a) 
StExpressionAssign a SrcSpan (Expression a) (Expression a) 
StPointerAssign a SrcSpan (Expression a) (Expression a) 
StLabelAssign a SrcSpan (Expression a) (Expression a) 
StGotoUnconditional a SrcSpan (Expression a) 
StGotoAssigned a SrcSpan (Expression a) (Maybe (AList Expression a)) 
StGotoComputed a SrcSpan (AList Expression a) (Expression a) 
StCall a SrcSpan (Expression a) (Maybe (AList Argument a)) 
StReturn a SrcSpan (Maybe (Expression a)) 
StContinue a SrcSpan 
StStop a SrcSpan (Maybe (Expression a)) 
StPause a SrcSpan (Maybe (Expression a)) 
StRead a SrcSpan (AList ControlPair a) (Maybe (AList Expression a)) 
StRead2 a SrcSpan (Expression a) (Maybe (AList Expression a)) 
StWrite a SrcSpan (AList ControlPair a) (Maybe (AList Expression a)) 
StPrint a SrcSpan (Expression a) (Maybe (AList Expression a)) 
StTypePrint a SrcSpan (Expression a) (Maybe (AList Expression a)) 
StOpen a SrcSpan (AList ControlPair a) 
StClose a SrcSpan (AList ControlPair a) 
StFlush a SrcSpan (AList FlushSpec a) 
StInquire a SrcSpan (AList ControlPair a) 
StRewind a SrcSpan (AList ControlPair a) 
StRewind2 a SrcSpan (Expression a) 
StBackspace a SrcSpan (AList ControlPair a) 
StBackspace2 a SrcSpan (Expression a) 
StEndfile a SrcSpan (AList ControlPair a) 
StEndfile2 a SrcSpan (Expression a) 
StAllocate a SrcSpan (Maybe (TypeSpec a)) (AList Expression a) (Maybe (AList AllocOpt a)) 
StNullify a SrcSpan (AList Expression a) 
StDeallocate a SrcSpan (AList Expression a) (Maybe (AList AllocOpt a)) 
StWhere a SrcSpan (Expression a) (Statement a) 
StWhereConstruct a SrcSpan (Maybe String) (Expression a) 
StElsewhere a SrcSpan (Maybe String) (Maybe (Expression a)) 
StEndWhere a SrcSpan (Maybe String) 
StUse a SrcSpan (Expression a) (Maybe ModuleNature) Only (Maybe (AList Use a)) 
StModuleProcedure a SrcSpan (AList Expression a) 
StProcedure a SrcSpan (Maybe (ProcInterface a)) (Maybe (Attribute a)) (AList ProcDecl a) 
StType a SrcSpan (Maybe (AList Attribute a)) String 
StEndType a SrcSpan (Maybe String) 
StSequence a SrcSpan 
StForall a SrcSpan (Maybe String) (ForallHeader a) 
StForallStatement a SrcSpan (ForallHeader a) (Statement a) 
StEndForall a SrcSpan (Maybe String) 
StImport a SrcSpan (AList Expression a) 
StEnum a SrcSpan 
StEnumerator a SrcSpan (AList Declarator a) 
StEndEnum a SrcSpan 
StFormatBogus a SrcSpan String 

Instances

Instances details
Functor Statement Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Conditioned Statement Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Statement Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Statement a -> Constr #

dataTypeOf :: Statement a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (Statement a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Statement a -> () #

Out a => Out (Statement a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Statement a -> Doc

doc :: Statement a -> Doc

docList :: [Statement a] -> Doc

Spanned (Statement a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Statement a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Statement a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Statement a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Statement a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Statement a) = D1 ('MetaData "Statement" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) ((((((C1 ('MetaCons "StDeclaration" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeSpec a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Attribute a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a))))) :+: C1 ('MetaCons "StStructure" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList StructureItem a))))) :+: (C1 ('MetaCons "StIntent" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Intent) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))) :+: (C1 ('MetaCons "StOptional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))) :+: C1 ('MetaCons "StPublic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a)))))))) :+: ((C1 ('MetaCons "StPrivate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))))) :+: (C1 ('MetaCons "StProtected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))))) :+: C1 ('MetaCons "StSave" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))))))) :+: (C1 ('MetaCons "StDimension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))) :+: (C1 ('MetaCons "StAllocatable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))) :+: C1 ('MetaCons "StAsynchronous" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))))))) :+: (((C1 ('MetaCons "StPointer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))) :+: C1 ('MetaCons "StTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a))))) :+: (C1 ('MetaCons "StValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))) :+: (C1 ('MetaCons "StVolatile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))) :+: C1 ('MetaCons "StData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList DataGroup a))))))) :+: ((C1 ('MetaCons "StAutomatic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))) :+: (C1 ('MetaCons "StNamelist" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Namelist a)))) :+: C1 ('MetaCons "StParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))))) :+: (C1 ('MetaCons "StExternal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))) :+: (C1 ('MetaCons "StIntrinsic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))) :+: C1 ('MetaCons "StCommon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList CommonGroup a))))))))) :+: ((((C1 ('MetaCons "StEquivalence" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList (AList Expression) a)))) :+: C1 ('MetaCons "StFormat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList FormatItem a))))) :+: (C1 ('MetaCons "StImplicit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList ImpList a))))) :+: (C1 ('MetaCons "StEntry" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))) :+: C1 ('MetaCons "StInclude" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Block a]))))))) :+: ((C1 ('MetaCons "StDo" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (DoSpecification a)))))) :+: (C1 ('MetaCons "StDoWhile" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))) :+: C1 ('MetaCons "StEnddo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))) :+: (C1 ('MetaCons "StCycle" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))) :+: (C1 ('MetaCons "StExit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))) :+: C1 ('MetaCons "StIfLogical" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Statement a)))))))) :+: (((C1 ('MetaCons "StIfArithmetic" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))) :+: C1 ('MetaCons "StIfThen" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))) :+: (C1 ('MetaCons "StElse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :+: (C1 ('MetaCons "StElsif" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "StEndif" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))))))) :+: ((C1 ('MetaCons "StSelectCase" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: (C1 ('MetaCons "StCase" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Index a))))) :+: C1 ('MetaCons "StEndcase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))) :+: (C1 ('MetaCons "StFunction" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))) :+: (C1 ('MetaCons "StExpressionAssign" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "StPointerAssign" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))))))))) :+: (((((C1 ('MetaCons "StLabelAssign" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "StGotoUnconditional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))) :+: (C1 ('MetaCons "StGotoAssigned" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))))) :+: (C1 ('MetaCons "StGotoComputed" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "StCall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Argument a)))))))) :+: ((C1 ('MetaCons "StReturn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))) :+: (C1 ('MetaCons "StContinue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: C1 ('MetaCons "StStop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))))) :+: (C1 ('MetaCons "StPause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))) :+: (C1 ('MetaCons "StRead" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ControlPair a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))))) :+: C1 ('MetaCons "StRead2" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))))))))) :+: (((C1 ('MetaCons "StWrite" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ControlPair a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))))) :+: C1 ('MetaCons "StPrint" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a)))))) :+: (C1 ('MetaCons "StTypePrint" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Expression a))))) :+: (C1 ('MetaCons "StOpen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ControlPair a)))) :+: C1 ('MetaCons "StClose" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ControlPair a))))))) :+: ((C1 ('MetaCons "StFlush" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList FlushSpec a)))) :+: (C1 ('MetaCons "StInquire" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ControlPair a)))) :+: C1 ('MetaCons "StRewind" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ControlPair a)))))) :+: (C1 ('MetaCons "StRewind2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: (C1 ('MetaCons "StBackspace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ControlPair a)))) :+: C1 ('MetaCons "StBackspace2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))))))) :+: ((((C1 ('MetaCons "StEndfile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ControlPair a)))) :+: C1 ('MetaCons "StEndfile2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))) :+: (C1 ('MetaCons "StAllocate" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TypeSpec a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList AllocOpt a)))))) :+: (C1 ('MetaCons "StNullify" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))) :+: C1 ('MetaCons "StDeallocate" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList AllocOpt a)))))))) :+: ((C1 ('MetaCons "StWhere" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Statement a)))) :+: (C1 ('MetaCons "StWhereConstruct" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "StElsewhere" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))))) :+: (C1 ('MetaCons "StEndWhere" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :+: (C1 ('MetaCons "StUse" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ModuleNature)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Only) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Use a)))))) :+: C1 ('MetaCons "StModuleProcedure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))))))) :+: (((C1 ('MetaCons "StProcedure" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ProcInterface a))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Attribute a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ProcDecl a))))) :+: (C1 ('MetaCons "StType" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Attribute a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "StEndType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))) :+: (C1 ('MetaCons "StSequence" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: (C1 ('MetaCons "StForall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ForallHeader a)))) :+: C1 ('MetaCons "StForallStatement" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ForallHeader a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Statement a))))))) :+: ((C1 ('MetaCons "StEndForall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :+: (C1 ('MetaCons "StImport" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))) :+: C1 ('MetaCons "StEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)))) :+: (C1 ('MetaCons "StEnumerator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))) :+: (C1 ('MetaCons "StEndEnum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: C1 ('MetaCons "StFormatBogus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))))))

data ProcDecl a Source #

Constructors

ProcDecl a SrcSpan (Expression a) (Maybe (Expression a)) 

Instances

Instances details
Functor ProcDecl Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated ProcDecl Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ProcDecl a -> Constr #

dataTypeOf :: ProcDecl a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: ProcDecl a -> String #

showList :: [ProcDecl a] -> ShowS #

Generic (ProcDecl a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: ProcDecl a -> () #

Out a => Out (ProcDecl a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> ProcDecl a -> Doc

doc :: ProcDecl a -> Doc

docList :: [ProcDecl a] -> Doc

Spanned (ProcDecl a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (ProcDecl a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (ProcDecl a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (ProcDecl a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ProcDecl a) Source # 
Instance details

Defined in Language.Fortran.AST

data ProcInterface a Source #

Instances

Instances details
Functor ProcInterface Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated ProcInterface Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ProcInterface a -> Constr #

dataTypeOf :: ProcInterface a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

Methods

rnf :: ProcInterface a -> () #

Out a => Out (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.AST

Spanned (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (ProcInterface a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (ProcInterface a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.AST

data ForallHeader a Source #

Instances

Instances details
Functor ForallHeader Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ForallHeader a -> Constr #

dataTypeOf :: ForallHeader a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (ForallHeader a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: ForallHeader a -> () #

Out a => Out (ForallHeader a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ForallHeader a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ForallHeader a) = D1 ('MetaData "ForallHeader" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (C1 ('MetaCons "ForallHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Name, Expression a, Expression a, Maybe (Expression a))]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))

data Only Source #

Constructors

Exclusive 
Permissive 

Instances

Instances details
Eq Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Data Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Only -> Constr #

dataTypeOf :: Only -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

showsPrec :: Int -> Only -> ShowS #

show :: Only -> String #

showList :: [Only] -> ShowS #

Generic Only Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep Only :: Type -> Type #

Methods

from :: Only -> Rep Only x #

to :: Rep Only x -> Only #

NFData Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: Only -> () #

Out Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Only -> Doc

doc :: Only -> Doc

docList :: [Only] -> Doc

Pretty Only Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

type Rep Only Source # 
Instance details

Defined in Language.Fortran.AST

type Rep Only = D1 ('MetaData "Only" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (C1 ('MetaCons "Exclusive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Permissive" 'PrefixI 'False) (U1 :: Type -> Type))

data ModuleNature Source #

Instances

Instances details
Eq ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

Data ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ModuleNature -> Constr #

dataTypeOf :: ModuleNature -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

Generic ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep ModuleNature :: Type -> Type #

NFData ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: ModuleNature -> () #

Out ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

type Rep ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

type Rep ModuleNature = D1 ('MetaData "ModuleNature" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (C1 ('MetaCons "ModIntrinsic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModNonIntrinsic" 'PrefixI 'False) (U1 :: Type -> Type))

data Use a Source #

Instances

Instances details
Functor Use Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated Use Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: Use a -> a Source #

setAnnotation :: a -> Use a -> Use a Source #

modifyAnnotation :: (a -> a) -> Use a -> Use a Source #

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Use a -> Constr #

dataTypeOf :: Use a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Use a -> String #

showList :: [Use a] -> ShowS #

Generic (Use a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Use a -> () #

Out a => Out (Use a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Use a -> Doc

doc :: Use a -> Doc

docList :: [Use a] -> Doc

Spanned (Use a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getSpan :: Use a -> SrcSpan Source #

setSpan :: SrcSpan -> Use a -> Use a Source #

Pretty (Use a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Methods

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

FirstParameter (Use a) a Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getFirstParameter :: Use a -> a Source #

setFirstParameter :: a -> Use a -> Use a Source #

SecondParameter (Use a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Use a) Source # 
Instance details

Defined in Language.Fortran.AST

data Argument a Source #

Constructors

Argument a SrcSpan (Maybe String) (Expression a) 

Instances

Instances details
Functor Argument Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated Argument Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Argument a -> Constr #

dataTypeOf :: Argument a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Argument a -> String #

showList :: [Argument a] -> ShowS #

Generic (Argument a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Argument a -> () #

Out a => Out (Argument a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Argument a -> Doc

doc :: Argument a -> Doc

docList :: [Argument a] -> Doc

Spanned (Argument a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Argument a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Argument a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Argument a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Argument a) Source # 
Instance details

Defined in Language.Fortran.AST

data Attribute a Source #

Instances

Instances details
Functor Attribute Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated Attribute Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Attribute a -> Constr #

dataTypeOf :: Attribute a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (Attribute a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Attribute a -> () #

Out a => Out (Attribute a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Attribute a -> Doc

doc :: Attribute a -> Doc

docList :: [Attribute a] -> Doc

Spanned (Attribute a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Attribute a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Attribute a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Attribute a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Attribute a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Attribute a) = D1 ('MetaData "Attribute" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) ((((C1 ('MetaCons "AttrAllocatable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: C1 ('MetaCons "AttrAsynchronous" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan))) :+: (C1 ('MetaCons "AttrDimension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList DimensionDeclarator a)))) :+: C1 ('MetaCons "AttrExternal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)))) :+: ((C1 ('MetaCons "AttrIntent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Intent))) :+: C1 ('MetaCons "AttrIntrinsic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan))) :+: (C1 ('MetaCons "AttrOptional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: C1 ('MetaCons "AttrParameter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan))))) :+: (((C1 ('MetaCons "AttrPointer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: C1 ('MetaCons "AttrPrivate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan))) :+: (C1 ('MetaCons "AttrProtected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: C1 ('MetaCons "AttrPublic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)))) :+: ((C1 ('MetaCons "AttrSave" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: C1 ('MetaCons "AttrSuffix" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Suffix a))))) :+: (C1 ('MetaCons "AttrTarget" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: (C1 ('MetaCons "AttrValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :+: C1 ('MetaCons "AttrVolatile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)))))))

data Intent Source #

Constructors

In 
Out 
InOut 

Instances

Instances details
Eq Intent Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Data Intent Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Intent -> Constr #

dataTypeOf :: Intent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Intent Source # 
Instance details

Defined in Language.Fortran.AST

Generic Intent Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep Intent :: Type -> Type #

Methods

from :: Intent -> Rep Intent x #

to :: Rep Intent x -> Intent #

NFData Intent Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: Intent -> () #

Out Intent Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Intent -> Doc

doc :: Intent -> Doc

docList :: [Intent] -> Doc

Pretty Intent Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

type Rep Intent Source # 
Instance details

Defined in Language.Fortran.AST

type Rep Intent = D1 ('MetaData "Intent" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (C1 ('MetaCons "In" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Out" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InOut" 'PrefixI 'False) (U1 :: Type -> Type)))

data ControlPair a Source #

Constructors

ControlPair a SrcSpan (Maybe String) (Expression a) 

Instances

Instances details
Functor ControlPair Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated ControlPair Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ControlPair a -> Constr #

dataTypeOf :: ControlPair a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (ControlPair a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: ControlPair a -> () #

Out a => Out (ControlPair a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> ControlPair a -> Doc

doc :: ControlPair a -> Doc

docList :: [ControlPair a] -> Doc

Spanned (ControlPair a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (ControlPair a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (ControlPair a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (ControlPair a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ControlPair a) Source # 
Instance details

Defined in Language.Fortran.AST

data AllocOpt a Source #

Instances

Instances details
Functor AllocOpt Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated AllocOpt Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: AllocOpt a -> Constr #

dataTypeOf :: AllocOpt a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: AllocOpt a -> String #

showList :: [AllocOpt a] -> ShowS #

Generic (AllocOpt a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: AllocOpt a -> () #

Out a => Out (AllocOpt a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> AllocOpt a -> Doc

doc :: AllocOpt a -> Doc

docList :: [AllocOpt a] -> Doc

Spanned (AllocOpt a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (AllocOpt a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (AllocOpt a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (AllocOpt a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (AllocOpt a) Source # 
Instance details

Defined in Language.Fortran.AST

data ImpList a Source #

Constructors

ImpList a SrcSpan (TypeSpec a) (AList ImpElement a) 

Instances

Instances details
Functor ImpList Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated ImpList Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ImpList a -> Constr #

dataTypeOf :: ImpList a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: ImpList a -> String #

showList :: [ImpList a] -> ShowS #

Generic (ImpList a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: ImpList a -> () #

Out a => Out (ImpList a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> ImpList a -> Doc

doc :: ImpList a -> Doc

docList :: [ImpList a] -> Doc

Spanned (ImpList a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (ImpList a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (ImpList a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (ImpList a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ImpList a) Source # 
Instance details

Defined in Language.Fortran.AST

data ImpElement a Source #

Instances

Instances details
Functor ImpElement Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated ImpElement Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: ImpElement a -> Constr #

dataTypeOf :: ImpElement a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (ImpElement a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: ImpElement a -> () #

Out a => Out (ImpElement a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> ImpElement a -> Doc

doc :: ImpElement a -> Doc

docList :: [ImpElement a] -> Doc

Spanned (ImpElement a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (ImpElement a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (ImpElement a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (ImpElement a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ImpElement a) Source # 
Instance details

Defined in Language.Fortran.AST

data CommonGroup a Source #

Instances

Instances details
Functor CommonGroup Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated CommonGroup Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: CommonGroup a -> Constr #

dataTypeOf :: CommonGroup a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (CommonGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: CommonGroup a -> () #

Out a => Out (CommonGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> CommonGroup a -> Doc

doc :: CommonGroup a -> Doc

docList :: [CommonGroup a] -> Doc

Spanned (CommonGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (CommonGroup a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (CommonGroup a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (CommonGroup a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (CommonGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

data Namelist a Source #

Constructors

Namelist a SrcSpan (Expression a) (AList Expression a) 

Instances

Instances details
Functor Namelist Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated Namelist Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Namelist a -> Constr #

dataTypeOf :: Namelist a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Namelist a -> String #

showList :: [Namelist a] -> ShowS #

Generic (Namelist a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Namelist a -> () #

Out a => Out (Namelist a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Namelist a -> Doc

doc :: Namelist a -> Doc

docList :: [Namelist a] -> Doc

Spanned (Namelist a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Namelist a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Namelist a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Namelist a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Namelist a) Source # 
Instance details

Defined in Language.Fortran.AST

data DataGroup a Source #

Instances

Instances details
Functor DataGroup Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated DataGroup Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: DataGroup a -> Constr #

dataTypeOf :: DataGroup a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (DataGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: DataGroup a -> () #

Out a => Out (DataGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> DataGroup a -> Doc

doc :: DataGroup a -> Doc

docList :: [DataGroup a] -> Doc

Spanned (DataGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (DataGroup a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (DataGroup a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (DataGroup a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (DataGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

data StructureItem a Source #

Instances

Instances details
Functor StructureItem Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated StructureItem Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: StructureItem a -> Constr #

dataTypeOf :: StructureItem a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

Methods

rnf :: StructureItem a -> () #

Out a => Out (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.AST

Spanned (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.AST

IndentablePretty (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (StructureItem a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (StructureItem a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (StructureItem a) = D1 ('MetaData "StructureItem" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (C1 ('MetaCons "StructFields" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeSpec a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Attribute a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a))))) :+: (C1 ('MetaCons "StructUnion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList UnionMap a)))) :+: C1 ('MetaCons "StructStructure" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList StructureItem a)))))))

data UnionMap a Source #

Constructors

UnionMap a SrcSpan (AList StructureItem a) 

Instances

Instances details
Functor UnionMap Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated UnionMap Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: UnionMap a -> Constr #

dataTypeOf :: UnionMap a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: UnionMap a -> String #

showList :: [UnionMap a] -> ShowS #

Generic (UnionMap a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: UnionMap a -> () #

Out a => Out (UnionMap a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> UnionMap a -> Doc

doc :: UnionMap a -> Doc

docList :: [UnionMap a] -> Doc

Spanned (UnionMap a) Source # 
Instance details

Defined in Language.Fortran.AST

IndentablePretty (UnionMap a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (UnionMap a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (UnionMap a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (UnionMap a) Source # 
Instance details

Defined in Language.Fortran.AST

data FormatItem a Source #

Instances

Instances details
Functor FormatItem Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated FormatItem Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: FormatItem a -> Constr #

dataTypeOf :: FormatItem a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (FormatItem a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: FormatItem a -> () #

Out a => Out (FormatItem a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> FormatItem a -> Doc

doc :: FormatItem a -> Doc

docList :: [FormatItem a] -> Doc

Spanned (FormatItem a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (FormatItem a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (FormatItem a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (FormatItem a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (FormatItem a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (FormatItem a) = D1 ('MetaData "FormatItem" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) ((C1 ('MetaCons "FIFormatList" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList FormatItem a)))) :+: (C1 ('MetaCons "FIHollerith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Value a)))) :+: C1 ('MetaCons "FIDelimiter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)))) :+: ((C1 ('MetaCons "FIFieldDescriptorDEFG" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))) :+: C1 ('MetaCons "FIFieldDescriptorAIL" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) :+: (C1 ('MetaCons "FIBlankDescriptor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))) :+: C1 ('MetaCons "FIScaleFactor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))))

data FlushSpec a Source #

Instances

Instances details
Functor FlushSpec Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated FlushSpec Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: FlushSpec a -> Constr #

dataTypeOf :: FlushSpec a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (FlushSpec a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: FlushSpec a -> () #

Out a => Out (FlushSpec a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> FlushSpec a -> Doc

doc :: FlushSpec a -> Doc

docList :: [FlushSpec a] -> Doc

Spanned (FlushSpec a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (FlushSpec a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (FlushSpec a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (FlushSpec a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (FlushSpec a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (FlushSpec a) = D1 ('MetaData "FlushSpec" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) ((C1 ('MetaCons "FSUnit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "FSIOStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))) :+: (C1 ('MetaCons "FSIOMsg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "FSErr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))))

data DoSpecification a Source #

Instances

Instances details
Functor DoSpecification Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated DoSpecification Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: DoSpecification a -> Constr #

dataTypeOf :: DoSpecification a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

Methods

rnf :: DoSpecification a -> () #

Out a => Out (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.AST

Spanned (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (DoSpecification a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (DoSpecification a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.AST

data Expression a Source #

Constructors

ExpValue a SrcSpan (Value a)

Use a value as an expression.

ExpBinary a SrcSpan BinaryOp (Expression a) (Expression a)

A binary operator applied to two expressions.

ExpUnary a SrcSpan UnaryOp (Expression a)

A unary operator applied to two expressions.

ExpSubscript a SrcSpan (Expression a) (AList Index a)

Array indexing

ExpDataRef a SrcSpan (Expression a) (Expression a)

% notation for variables inside data types

ExpFunctionCall a SrcSpan (Expression a) (Maybe (AList Argument a))

A function expression applied to a list of arguments.

ExpImpliedDo a SrcSpan (AList Expression a) (DoSpecification a)

Implied do (i.e. one-liner do loops)

ExpInitialisation a SrcSpan (AList Expression a)

Array initialisation

ExpReturnSpec a SrcSpan (Expression a)

Function return value specification

Instances

Instances details
Functor Expression Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated Expression Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Expression a -> Constr #

dataTypeOf :: Expression a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (Expression a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Expression a -> () #

Out a => Out (Expression a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Expression a -> Doc

doc :: Expression a -> Doc

docList :: [Expression a] -> Doc

Spanned (Expression a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Expression a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Expression a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Expression a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Expression a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Expression a) = D1 ('MetaData "Expression" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (((C1 ('MetaCons "ExpValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Value a)))) :+: C1 ('MetaCons "ExpBinary" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BinaryOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))))) :+: (C1 ('MetaCons "ExpUnary" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "ExpSubscript" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Index a)))))) :+: ((C1 ('MetaCons "ExpDataRef" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :+: C1 ('MetaCons "ExpFunctionCall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (AList Argument a)))))) :+: (C1 ('MetaCons "ExpImpliedDo" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DoSpecification a)))) :+: (C1 ('MetaCons "ExpInitialisation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))) :+: C1 ('MetaCons "ExpReturnSpec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))))))

data Index a Source #

Instances

Instances details
Functor Index Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated Index Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: Index a -> a Source #

setAnnotation :: a -> Index a -> Index a Source #

modifyAnnotation :: (a -> a) -> Index a -> Index a Source #

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Index a -> Constr #

dataTypeOf :: Index a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Index a -> String #

showList :: [Index a] -> ShowS #

Generic (Index a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Index a -> () #

Out a => Out (Index a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Index a -> Doc

doc :: Index a -> Doc

docList :: [Index a] -> Doc

Spanned (Index a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Index a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Index a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Index a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Index a) Source # 
Instance details

Defined in Language.Fortran.AST

data Value a Source #

Constructors

ValInteger String

The string representation of an integer literal

ValReal String

The string representation of a real literal

ValComplex (Expression a) (Expression a)

The real and imaginary parts of a complex value

ValString String

A string literal

ValHollerith String

A Hollerith literal

ValVariable Name

The name of a variable

ValIntrinsic Name

The name of a built-in function

ValLogical String

A boolean value

ValOperator String

User-defined operators in interfaces

ValAssignment

Overloaded assignment in interfaces

ValType String 
ValStar 
ValColon 

Instances

Instances details
Functor Value Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Value a -> Constr #

dataTypeOf :: Value a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Methods

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

show :: Value a -> String #

showList :: [Value a] -> ShowS #

Generic (Value a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Value a -> () #

Out a => Out (Value a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Value a -> Doc

doc :: Value a -> Doc

docList :: [Value a] -> Doc

Pretty (Value a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Value a) String Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

type Rep (Value a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Value a) = D1 ('MetaData "Value" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (((C1 ('MetaCons "ValInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "ValReal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ValComplex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a))))) :+: (C1 ('MetaCons "ValString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "ValHollerith" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ValVariable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))))) :+: ((C1 ('MetaCons "ValIntrinsic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: (C1 ('MetaCons "ValLogical" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ValOperator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "ValAssignment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "ValStar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValColon" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Declarator a Source #

Instances

Instances details
Functor Declarator Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated Declarator Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: Declarator a -> Constr #

dataTypeOf :: Declarator a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST

Generic (Declarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST

Methods

rnf :: Declarator a -> () #

Out a => Out (Declarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Declarator a -> Doc

doc :: Declarator a -> Doc

docList :: [Declarator a] -> Doc

Spanned (Declarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (Declarator a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (Declarator a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (Declarator a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Declarator a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (Declarator a) = D1 ('MetaData "Declarator" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) (C1 ('MetaCons "DeclVariable" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))) :+: C1 ('MetaCons "DeclArray" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList DimensionDeclarator a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))))

data DimensionDeclarator a Source #

Instances

Instances details
Functor DimensionDeclarator Source # 
Instance details

Defined in Language.Fortran.AST

Annotated DimensionDeclarator Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

toConstr :: DimensionDeclarator a -> Constr #

dataTypeOf :: DimensionDeclarator a -> DataType #

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

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DimensionDeclarator a)) #

gmapT :: (forall b. Data b => b -> b) -> DimensionDeclarator a -> DimensionDeclarator a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DimensionDeclarator a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DimensionDeclarator a -> r #

gmapQ :: (forall d. Data d => d -> u) -> DimensionDeclarator a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DimensionDeclarator a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DimensionDeclarator a -> m (DimensionDeclarator a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionDeclarator a -> m (DimensionDeclarator a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DimensionDeclarator a -> m (DimensionDeclarator a) #

Show a => Show (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Generic (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep (DimensionDeclarator a) :: Type -> Type #

NFData a => NFData (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: DimensionDeclarator a -> () #

Out a => Out (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Spanned (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Pretty (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

FirstParameter (DimensionDeclarator a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (DimensionDeclarator a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.AST

data UnaryOp Source #

Constructors

Plus 
Minus 
Not 
UnCustom String 

Instances

Instances details
Eq UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

(==) :: UnaryOp -> UnaryOp -> Bool #

(/=) :: UnaryOp -> UnaryOp -> Bool #

Data UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnaryOp -> c UnaryOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnaryOp #

toConstr :: UnaryOp -> Constr #

dataTypeOf :: UnaryOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnaryOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnaryOp) #

gmapT :: (forall b. Data b => b -> b) -> UnaryOp -> UnaryOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> UnaryOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnaryOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp #

Ord UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Show UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Generic UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep UnaryOp :: Type -> Type #

Methods

from :: UnaryOp -> Rep UnaryOp x #

to :: Rep UnaryOp x -> UnaryOp #

Binary UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

put :: UnaryOp -> Put #

get :: Get UnaryOp #

putList :: [UnaryOp] -> Put #

NFData UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: UnaryOp -> () #

Out UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> UnaryOp -> Doc

doc :: UnaryOp -> Doc

docList :: [UnaryOp] -> Doc

Pretty UnaryOp Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

type Rep UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

type Rep UnaryOp = D1 ('MetaData "UnaryOp" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) ((C1 ('MetaCons "Plus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Minus" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Not" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnCustom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

data BinaryOp Source #

Instances

Instances details
Eq BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Data BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinaryOp -> c BinaryOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinaryOp #

toConstr :: BinaryOp -> Constr #

dataTypeOf :: BinaryOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinaryOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinaryOp) #

gmapT :: (forall b. Data b => b -> b) -> BinaryOp -> BinaryOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinaryOp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinaryOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> BinaryOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BinaryOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp #

Ord BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Show BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Generic BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep BinaryOp :: Type -> Type #

Methods

from :: BinaryOp -> Rep BinaryOp x #

to :: Rep BinaryOp x -> BinaryOp #

Binary BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

put :: BinaryOp -> Put #

get :: Get BinaryOp #

putList :: [BinaryOp] -> Put #

NFData BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: BinaryOp -> () #

Out BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> BinaryOp -> Doc

doc :: BinaryOp -> Doc

docList :: [BinaryOp] -> Doc

Pretty BinaryOp Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

type Rep BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

type Rep BinaryOp = D1 ('MetaData "BinaryOp" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) ((((C1 ('MetaCons "Addition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Subtraction" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Multiplication" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Division" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Exponentiation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Concatenation" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GTE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "LTE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "XOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Equivalent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NotEquivalent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinCustom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))))

class Annotated f where Source #

Minimal complete definition

Nothing

Methods

getAnnotation :: f a -> a Source #

default getAnnotation :: FirstParameter (f a) a => f a -> a Source #

setAnnotation :: a -> f a -> f a Source #

default setAnnotation :: FirstParameter (f a) a => a -> f a -> f a Source #

modifyAnnotation :: (a -> a) -> f a -> f a Source #

Instances

Instances details
Annotated DimensionDeclarator Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Declarator Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Index Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: Index a -> a Source #

setAnnotation :: a -> Index a -> Index a Source #

modifyAnnotation :: (a -> a) -> Index a -> Index a Source #

Annotated Expression Source # 
Instance details

Defined in Language.Fortran.AST

Annotated DoSpecification Source # 
Instance details

Defined in Language.Fortran.AST

Annotated FlushSpec Source # 
Instance details

Defined in Language.Fortran.AST

Annotated FormatItem Source # 
Instance details

Defined in Language.Fortran.AST

Annotated UnionMap Source # 
Instance details

Defined in Language.Fortran.AST

Annotated StructureItem Source # 
Instance details

Defined in Language.Fortran.AST

Annotated DataGroup Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Namelist Source # 
Instance details

Defined in Language.Fortran.AST

Annotated CommonGroup Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ImpElement Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ImpList Source # 
Instance details

Defined in Language.Fortran.AST

Annotated AllocOpt Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ControlPair Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Attribute Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Argument Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Use Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: Use a -> a Source #

setAnnotation :: a -> Use a -> Use a Source #

modifyAnnotation :: (a -> a) -> Use a -> Use a Source #

Annotated ProcInterface Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ProcDecl Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Statement Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Block Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: Block a -> a Source #

setAnnotation :: a -> Block a -> Block a Source #

modifyAnnotation :: (a -> a) -> Block a -> Block a Source #

Annotated ProgramUnit Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Selector Source # 
Instance details

Defined in Language.Fortran.AST

Annotated TypeSpec Source # 
Instance details

Defined in Language.Fortran.AST

Annotated LValue Source # 
Instance details

Defined in Language.Fortran.LValue

Methods

getAnnotation :: LValue a -> a Source #

setAnnotation :: a -> LValue a -> LValue a Source #

modifyAnnotation :: (a -> a) -> LValue a -> LValue a Source #

Annotated (AList t) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: AList t a -> a Source #

setAnnotation :: a -> AList t a -> AList t a Source #

modifyAnnotation :: (a -> a) -> AList t a -> AList t a Source #

class (Spanned a, Spanned b) => SpannedPair a b where Source #

Methods

getTransSpan :: a -> b -> SrcSpan Source #

Instances

Instances details
(Spanned a, Spanned b) => SpannedPair a b Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getTransSpan :: a -> b -> SrcSpan Source #

(Spanned a, Spanned b) => SpannedPair a [[b]] Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getTransSpan :: a -> [[b]] -> SrcSpan Source #

(Spanned a, Spanned b) => SpannedPair a [b] Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getTransSpan :: a -> [b] -> SrcSpan Source #

class Labeled f where Source #

Methods

getLabel :: f a -> Maybe (Expression a) Source #

getLastLabel :: f a -> Maybe (Expression a) Source #

setLabel :: f a -> Expression a -> f a Source #

Instances

Instances details
Labeled Block Source # 
Instance details

Defined in Language.Fortran.AST

class Conditioned f where Source #

Methods

getCondition :: f a -> Maybe (Expression a) Source #

Instances

Instances details
Conditioned Statement Source # 
Instance details

Defined in Language.Fortran.AST

Conditioned Block Source # 
Instance details

Defined in Language.Fortran.AST

data ProgramUnitName Source #

Instances

Instances details
Eq ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Data ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProgramUnitName -> c ProgramUnitName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProgramUnitName #

toConstr :: ProgramUnitName -> Constr #

dataTypeOf :: ProgramUnitName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProgramUnitName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProgramUnitName) #

gmapT :: (forall b. Data b => b -> b) -> ProgramUnitName -> ProgramUnitName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProgramUnitName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProgramUnitName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProgramUnitName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProgramUnitName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProgramUnitName -> m ProgramUnitName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProgramUnitName -> m ProgramUnitName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProgramUnitName -> m ProgramUnitName #

Ord ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Show ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Generic ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep ProgramUnitName :: Type -> Type #

Binary ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

NFData ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: ProgramUnitName -> () #

type Rep ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

type Rep ProgramUnitName = D1 ('MetaData "ProgramUnitName" "Language.Fortran.AST" "fortran-src-0.4.2-inplace" 'False) ((C1 ('MetaCons "Named" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "NamelessBlockData" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NamelessComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamelessMain" 'PrefixI 'False) (U1 :: Type -> Type)))

class Named a where Source #

Instances

Instances details
Named (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.AST

Orphan instances

NFData FortranVersion Source # 
Instance details

Methods

rnf :: FortranVersion -> () #

Out FortranVersion Source # 
Instance details

Spanned a => Spanned [a] Source # 
Instance details

Methods

getSpan :: [a] -> SrcSpan Source #

setSpan :: SrcSpan -> [a] -> [a] Source #

(Spanned a, Spanned b) => Spanned (Either a b) Source # 
Instance details

Methods

getSpan :: Either a b -> SrcSpan Source #

setSpan :: SrcSpan -> Either a b -> Either a b Source #

(Spanned a, Spanned b) => Spanned (Maybe a, b) Source # 
Instance details

Methods

getSpan :: (Maybe a, b) -> SrcSpan Source #

setSpan :: SrcSpan -> (Maybe a, b) -> (Maybe a, b) Source #

(Spanned a, Spanned b) => Spanned (a, b) Source # 
Instance details

Methods

getSpan :: (a, b) -> SrcSpan Source #

setSpan :: SrcSpan -> (a, b) -> (a, b) Source #

(Spanned a, Spanned b) => Spanned (a, Maybe b) Source # 
Instance details

Methods

getSpan :: (a, Maybe b) -> SrcSpan Source #

setSpan :: SrcSpan -> (a, Maybe b) -> (a, Maybe b) Source #

(Spanned a, Spanned b, Spanned c) => Spanned (Maybe a, b, c) Source # 
Instance details

Methods

getSpan :: (Maybe a, b, c) -> SrcSpan Source #

setSpan :: SrcSpan -> (Maybe a, b, c) -> (Maybe a, b, c) Source #

(Spanned a, Spanned b, Spanned c) => Spanned (Maybe a, Maybe b, Maybe c) Source # 
Instance details

Methods

getSpan :: (Maybe a, Maybe b, Maybe c) -> SrcSpan Source #

setSpan :: SrcSpan -> (Maybe a, Maybe b, Maybe c) -> (Maybe a, Maybe b, Maybe c) Source #

(Spanned a, Spanned b, Spanned c) => Spanned (a, b, c) Source # 
Instance details

Methods

getSpan :: (a, b, c) -> SrcSpan Source #

setSpan :: SrcSpan -> (a, b, c) -> (a, b, c) Source #

(Spanned a, Spanned b, Spanned c) => Spanned (a, Maybe b, Maybe c) Source # 
Instance details

Methods

getSpan :: (a, Maybe b, Maybe c) -> SrcSpan Source #

setSpan :: SrcSpan -> (a, Maybe b, Maybe c) -> (a, Maybe b, Maybe c) Source #