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

Language.Fortran.AST

Description

Data types for representing Fortran code (for various versions of Fortran).

The same representation is used for all supported Fortran standards. Constructs only available in certain versions are gated by the parsers (and the pretty printer). In general, the definitions here are highly permissible, partly to allow for all the oddities of older standards & extensions.

Useful Fortran standard references:

  • Fortran 2018 standard: WD 1539-1 J3/18-007r1
  • Fortran 2008 standard: WD 1539-1 J3/10-007r1
  • Fortran 90 standard: ANSI X3.198-1992 (also ISO/IEC 1539:1991)
  • Fortran 90 Handbook (J. Adams)
  • Fortran 77 standard: ANSI X3.9-1978
Synopsis

AST nodes and types

Statements and expressions

data ProgramFile a Source #

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 #

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: ProgramFile a -> () #

IndentablePretty (ProgramFile a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (ProgramFile a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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.15.1-inplace" 'False) (C1 ('MetaCons "ProgramFile" 'PrefixI 'True) (S1 ('MetaSel ('Just "programFileMeta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MetaInfo) :*: S1 ('MetaSel ('Just "programFileProgramUnits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ProgramUnit a])))

data ProgramUnit a Source #

A Fortran program unit. _(F2008 2.2)_

A Fortran program is made up of many program units.

Related points from the Fortran 2008 specification:

  • There must be exactly one main program, and any number of other program units.
  • Note 2.3: There may be at most 1 unnamed block data program unit.

Constructors

PUMain

Main program

Fields

PUModule

Module

Fields

PUSubroutine

Subroutine subprogram (procedure)

Fields

PUFunction

Function subprogram (procedure)

Fields

PUBlockData

Block data (named or unnamed).

Fields

PUComment a SrcSpan (Comment a)

Program unit-level comment

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: ProgramUnit a -> () #

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

Spanned (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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.15.1-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 Block a Source #

Constructors

BlStatement

Statement

Fields

BlForall

FORALL array assignment syntax

Fields

BlIf

IF block construct

Fields

BlCase

SELECT CASE construct

Fields

BlDo 

Fields

BlDoWhile 

Fields

BlAssociate

The first Expression in the abbreviation tuple is always an ExpValue _ _ (ValVariable id). Also guaranteed nonempty. TODO

Fields

BlInterface 

Fields

BlComment a SrcSpan (Comment a)

Block-level comment

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 #

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 #

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Block a -> () #

IndentablePretty (Block a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty [Block a] Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Block a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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.15.1-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 (NonEmpty (Expression a, [Block a])))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [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 [(AList Index a, [Block a])])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [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 "BlAssociate" '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 (AList (ATuple Expression 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

Declare variable(s) at a given type.

Fields

StStructure

A structure (pre-F90 extension) declaration.

Fields

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

SAVE statement: variable retains its value between invocations

Fields

StDimension a SrcSpan (AList Declarator a)

DIMENSION attribute as statement.

StAllocatable a SrcSpan (AList Declarator a)

ALLOCATABLE attribute statement.

StAsynchronous a SrcSpan (AList Declarator a)

ASYNCHRONOUS attribute statement.

StPointer a SrcSpan (AList Declarator a)

POINTER attribute statement.

StTarget a SrcSpan (AList Declarator a)

TARGET attribute statement.

StValue a SrcSpan (AList Declarator a)

VALUE attribute statement.

StVolatile a SrcSpan (AList Declarator a)

VOLATILE attribute statement.

StData a SrcSpan (AList DataGroup a) 
StAutomatic a SrcSpan (AList Declarator a) 
StStatic a SrcSpan (AList Declarator a) 
StNamelist a SrcSpan (AList Namelist a) 
StParameter a SrcSpan (AList Declarator a)

PARAMETER attribute as statement.

StExternal a SrcSpan (AList Expression a) 
StIntrinsic a SrcSpan (AList Expression a) 
StCommon a SrcSpan (AList CommonGroup a)

A COMMON statement, defining a list of common blocks.

StEquivalence a SrcSpan (AList (AList Expression) a) 
StFormat a SrcSpan (AList FormatItem a) 
StImplicit a SrcSpan (Maybe (AList ImpList a)) 
StEntry 

Fields

StInclude 

Fields

  • a
     
  • SrcSpan
     
  • (Expression a)

    file name to include. guaranteed ExpValue ValString

  • (Maybe [Block a])

    First parsed to Nothing, then potentially "expanded out" in a post-parse step.

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))

guaranteed ExpValue ValVariable

StExit a SrcSpan (Maybe (Expression a)) 
StIfLogical 

Fields

StIfArithmetic a SrcSpan (Expression a) (Expression a) (Expression a) (Expression a) 
StSelectCase

CASE construct opener.

Fields

StCase

inner CASE clause

Fields

StEndcase

END SELECT statement

Fields

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) (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

Special TYPE "print" statement (~F77 syntactic sugar for PRINT/WRITE)

Not to be confused with the TYPE construct in later standards for defining derived data types.

Fields

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

ALLOCATE: associate pointers with targets

Fields

StNullify

NULLIFY: disassociate pointers from targets

Fields

StDeallocate

DEALLOCATE: disassociate pointers from targets

Fields

StWhere 

Fields

StWhereConstruct

begin WHERE block

Fields

StElsewhere

WHERE clause. compare to IF, IF ELSE

Fields

StEndWhere

end WHERE block

Fields

StUse

Import definitions (procedures, types) from a module. (F2018 14.2.2)

If a module nature isn't provided and there are both intrinsic and nonintrinsic modules with that name, the nonintrinsic module is selected.

Fields

StModuleProcedure a SrcSpan (AList Expression a)

procedure names, guaranteed ExpValue ValVariable

StProcedure a SrcSpan (Maybe (ProcInterface a)) (Maybe (AList Attribute a)) (AList ProcDecl a) 
StType

TYPE ... = begin a DDT (derived data type) definition block

Fields

StEndType

END TYPE [ type-name ] = end a DDT definition block

Fields

StSequence a SrcSpan 
StForall

FORALL ... = begin a FORALL block

Fields

StEndForall

END FORALL [ construct-name ]

Fields

StForallStatement

FORALL statement - essentially an inline FORALL block

Fields

StImport a SrcSpan (AList Expression a)

guaranteed ExpValue ValVariable

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 #

Annotated Statement Source # 
Instance details

Defined in Language.Fortran.AST

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: Statement a -> () #

Pretty (Statement a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Statement a) 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 #

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.15.1-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 "StStatic" '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 "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 (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 (AList 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 "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 "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 "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 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 one expression.

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) (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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: Expression a -> () #

Pretty (Expression a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Expression a) 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 #

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.15.1-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 (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 #

Constructors

IxSingle a SrcSpan (Maybe String) (Expression a) 
IxRange 

Fields

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 #

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Index a -> () #

Pretty (Index a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Index a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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 #

Values and literals.

Note that KindParam kind parameters may only be available on certain Fortran parsers. The fixed form parsers (F77, F66) may not parse them.

Constructors

ValInteger String (Maybe (KindParam a))

The string representation of an integer literal

ValReal RealLit (Maybe (KindParam a))

The string representation of a real literal

ValComplex (ComplexLit a)

The real and imaginary parts of a complex literal (real, imag).

ValString String

A string literal

ValBoz Boz

A BOZ literal constant

ValHollerith String

A Hollerith literal

ValVariable Name

The name of a variable

ValIntrinsic Name

The name of a built-in function

ValLogical Bool (Maybe (KindParam a))

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 #

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Value a -> () #

Pretty (Value a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

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

Defined in Language.Fortran.AST

Methods

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

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

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.15.1-inplace" 'False) (((C1 ('MetaCons "ValInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (KindParam a)))) :+: (C1 ('MetaCons "ValReal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RealLit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (KindParam a)))) :+: C1 ('MetaCons "ValComplex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ComplexLit a))))) :+: ((C1 ('MetaCons "ValString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ValBoz" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Boz))) :+: (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 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (KindParam a)))) :+: 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 KindParam a Source #

Constructors

KindParamInt a SrcSpan String
[0-9]+
KindParamVar a SrcSpan Name

[a-z][a-z0-9]+ (case insensitive)

Instances

Instances details
Functor KindParam Source # 
Instance details

Defined in Language.Fortran.AST.Literal

Methods

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

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

Annotated KindParam Source # 
Instance details

Defined in Language.Fortran.AST.Literal

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

Defined in Language.Fortran.AST.Literal

Methods

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

doc :: KindParam a -> Doc #

docList :: [KindParam a] -> Doc #

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

Defined in Language.Fortran.AST.Literal

Methods

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

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

toConstr :: KindParam a -> Constr #

dataTypeOf :: KindParam a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (KindParam a) Source # 
Instance details

Defined in Language.Fortran.AST.Literal

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST.Literal

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

Defined in Language.Fortran.AST.Literal

Methods

rnf :: KindParam a -> () #

Pretty (KindParam a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (KindParam a) Source # 
Instance details

Defined in Language.Fortran.AST.Literal

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

Defined in Language.Fortran.AST.Literal

Methods

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

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

FirstParameter (KindParam a) a Source # 
Instance details

Defined in Language.Fortran.AST.Literal

SecondParameter (KindParam a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST.Literal

type Rep (KindParam a) Source # 
Instance details

Defined in Language.Fortran.AST.Literal

data ComplexPart a Source #

A part (either real or imaginary) of a complex literal.

Since Fortran 2003, complex literal parts support named constants, which must be resolved in context at compile time (R422, R423).

Some compilers also allow constant expressions for the parts, and must evaluate at compile time. That's not allowed in any standard. Apparently, gfortran and ifort don't allow it, while nvfortran does. See: https://fortran-lang.discourse.group/t/complex-constants-and-variables/2909/3

We specifically avoid supporting that by defining complex parts without being mutually recursive with Expression.

Constructors

ComplexPartReal a SrcSpan RealLit (Maybe (KindParam a))

signed real lit

ComplexPartInt a SrcSpan String (Maybe (KindParam a))

signed int lit

ComplexPartNamed a SrcSpan Name

named constant

Instances

Instances details
Functor ComplexPart Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

Methods

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

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

Annotated ComplexPart Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

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

Defined in Language.Fortran.AST.Literal.Complex

Methods

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

doc :: ComplexPart a -> Doc #

docList :: [ComplexPart a] -> Doc #

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

Defined in Language.Fortran.AST.Literal.Complex

Methods

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

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

toConstr :: ComplexPart a -> Constr #

dataTypeOf :: ComplexPart a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (ComplexPart a) Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST.Literal.Complex

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

Defined in Language.Fortran.AST.Literal.Complex

Methods

rnf :: ComplexPart a -> () #

Pretty (ComplexPart a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (ComplexPart a) Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

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

Defined in Language.Fortran.AST.Literal.Complex

FirstParameter (ComplexPart a) a Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

SecondParameter (ComplexPart a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

type Rep (ComplexPart a) Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

type Rep (ComplexPart a) = D1 ('MetaData "ComplexPart" "Language.Fortran.AST.Literal.Complex" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "ComplexPartReal" '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 RealLit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (KindParam a))))) :+: (C1 ('MetaCons "ComplexPartInt" '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) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (KindParam a))))) :+: C1 ('MetaCons "ComplexPartNamed" '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)))))

data UnaryOp Source #

Constructors

Plus 
Minus 
Not 
UnCustom String 

Instances

Instances details
Out UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> UnaryOp -> Doc #

doc :: UnaryOp -> Doc #

docList :: [UnaryOp] -> Doc #

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 #

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 #

Show UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

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 -> () #

Pretty UnaryOp Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Eq UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Ord UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

type Rep UnaryOp Source # 
Instance details

Defined in Language.Fortran.AST

type Rep UnaryOp = D1 ('MetaData "UnaryOp" "Language.Fortran.AST" "fortran-src-0.15.1-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
Out BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> BinaryOp -> Doc #

doc :: BinaryOp -> Doc #

docList :: [BinaryOp] -> Doc #

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 #

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 #

Show BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

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 -> () #

Pretty BinaryOp Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Eq BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

Ord BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

type Rep BinaryOp Source # 
Instance details

Defined in Language.Fortran.AST

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

Types and declarations

data BaseType Source #

Type name referenced in syntax.

In many Fortran specs and compilers, certain types are actually "synonyms" for other types with specified kinds. The primary example is DOUBLE PRECISION being equivalent to REAL(8). Type kinds were introduced in Fortran 90, and it should be safe to replace all instances of DOUBLE PRECISION with REAL(8) in Fortran 90 code. However, type kinds weren't present in (standard) Fortran 77, so this equivalence was detached from the user.

In any case, it's unclear how strong the equivalence is and whether it can be retroactively applied to previous standards. We choose to parse types directly, and handle those transformations during type analysis, where we assign most scalars a kind (see SemType).

Instances

Instances details
Out BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> BaseType -> Doc #

doc :: BaseType -> Doc #

docList :: [BaseType] -> Doc #

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 #

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 #

Show BaseType Source # 
Instance details

Defined in Language.Fortran.AST

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 -> () #

Pretty BaseType Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Eq BaseType Source # 
Instance details

Defined in Language.Fortran.AST

Ord BaseType Source # 
Instance details

Defined in Language.Fortran.AST

type Rep BaseType Source # 
Instance details

Defined in Language.Fortran.AST

type Rep BaseType = D1 ('MetaData "BaseType" "Language.Fortran.AST" "fortran-src-0.15.1-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) (U1 :: Type -> Type) :+: 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 TypeSpec a Source #

The type specification of a declaration statement, containing the syntactic type name and kind selector.

See HP's F90 spec pg.24.

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

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: TypeSpec a -> () #

Pretty (TypeSpec a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (TypeSpec a) 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 #

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

type Rep (TypeSpec a) = D1 ('MetaData "TypeSpec" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "TypeSpec" 'PrefixI 'True) ((S1 ('MetaSel ('Just "typeSpecAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "typeSpecSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "typeSpecBaseType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BaseType) :*: S1 ('MetaSel ('Just "typeSpecSelector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Selector a))))))

data Selector a Source #

The "kind selector" of a declaration statement. Tightly bound to TypeSpec.

HP's F90 spec (pg.24) actually differentiates between "kind selectors" and "char selectors", where char selectors can specify a length (alongside kind), and the default meaning of an unlabelled kind parameter (the 8 in INTEGER(8)) is length instead of kind. We handle this correctly in the parsers, but place both into this Selector type.

The upshot is, length is invalid for non-CHARACTER types, and the parser guarantees that it will be Nothing. For CHARACTER types, both maybe or may not be present.

Often used with the assumption that when a Selector term is present, it contains some information (i.e. one of length or kind is Just _), so that the awkward "empty" possibility may be avoided.

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

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Selector a -> () #

Pretty (Selector a) Source #

Note that this instance is tightly bound with TypeSpec due to Selector appending information on where TypeSpec should have been prettied. By itself, this instance is less sensible.

Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Selector a) 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 #

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

type Rep (Selector a) = D1 ('MetaData "Selector" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "Selector" 'PrefixI 'True) ((S1 ('MetaSel ('Just "selectorAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "selectorSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "selectorLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Just "selectorKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))))

data Declarator a Source #

Declarators. R505 entity-decl from F90 ISO spec.

Declaration statements can have multiple variables on the right of the double colon, separated by commas. A Declarator identifies a single one of these. In F90, they look like this:

VAR_NAME ( OPT_ARRAY_DIMS ) * CHAR_LENGTH_EXPR = INIT_EXPR

F77 doesn't standardize so nicely -- in particular, I'm not confident in initializing expression syntax. So no example.

Only CHARACTERs may specify a length. However, a nonstandard syntax feature uses non-CHARACTER lengths as a kind parameter. We parse regardless of type and warn during analysis.

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: Declarator a -> () #

Pretty (Declarator a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Declarator a) 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 #

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.15.1-inplace" 'False) (C1 ('MetaCons "Declarator" 'PrefixI 'True) ((S1 ('MetaSel ('Just "declaratorAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "declaratorSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Just "declaratorVariable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))) :*: (S1 ('MetaSel ('Just "declaratorType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclaratorType a)) :*: (S1 ('MetaSel ('Just "declaratorLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Just "declaratorInitial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))))

data DeclaratorType a Source #

Instances

Instances details
Functor DeclaratorType Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

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

Defined in Language.Fortran.AST

Data a => Data (DeclaratorType 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) -> DeclaratorType a -> c (DeclaratorType a) #

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

toConstr :: DeclaratorType a -> Constr #

dataTypeOf :: DeclaratorType a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (DeclaratorType a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: DeclaratorType a -> () #

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

Defined in Language.Fortran.AST

type Rep (DeclaratorType a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (DeclaratorType a) = D1 ('MetaData "DeclaratorType" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "ScalarDecl" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ArrayDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList DimensionDeclarator a))))

data DimensionDeclarator a Source #

Dimension declarator stored in dimension attributes and Declarators.

Instances

Instances details
Functor DimensionDeclarator Source # 
Instance details

Defined in Language.Fortran.AST

Annotated DimensionDeclarator Source # 
Instance details

Defined in Language.Fortran.AST

Out a => Out (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) #

Generic (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: DimensionDeclarator a -> () #

Pretty (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

type Rep (DimensionDeclarator a) = D1 ('MetaData "DimensionDeclarator" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "DimensionDeclarator" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dimDeclAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "dimDeclSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "dimDeclLower") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Just "dimDeclUpper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))))

Annotated node list (re-export)

Other

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: Attribute a -> () #

Pretty (Attribute a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Attribute a) 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 #

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.15.1-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 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 #

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Prefix a -> () #

Spanned (Prefix a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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 #

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Suffix a -> () #

Pretty (Suffix a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Suffix a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

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

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

data ProcDecl a Source #

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

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: ProcDecl a -> () #

Pretty (ProcDecl a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (ProcDecl a) 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 #

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

type Rep (ProcDecl a) = D1 ('MetaData "ProcDecl" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "ProcDecl" 'PrefixI 'True) ((S1 ('MetaSel ('Just "procDeclAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "procDeclSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "procDeclEntityName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "procDeclInitName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))))

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

Out a => Out (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) #

Generic (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: ProcInterface a -> () #

Pretty (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

newtype Comment a Source #

Constructors

Comment String 

Instances

Instances details
Functor (Comment :: TYPE LiftedRep -> TYPE LiftedRep) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

(<$) :: a -> Comment b -> 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 #

(Typeable a, Typeable k) => 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) #

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Comment a -> () #

Eq (Comment a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

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.15.1-inplace" 'True) (C1 ('MetaCons "Comment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data ForallHeader a Source #

Part of a FORALL statement. Introduced in Fortran 95.

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 #

Annotated ForallHeader Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

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

doc :: ForallHeader a -> Doc #

docList :: [ForallHeader a] -> Doc #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: ForallHeader a -> () #

Spanned (ForallHeader a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

FirstParameter (ForallHeader a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (ForallHeader a) SrcSpan 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.15.1-inplace" 'False) (C1 ('MetaCons "ForallHeader" 'PrefixI 'True) ((S1 ('MetaSel ('Just "forallHeaderAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "forallHeaderSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "forallHeaderHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ForallHeaderPart a]) :*: S1 ('MetaSel ('Just "forallHeaderScaling") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))))))

data ForallHeaderPart a Source #

Instances

Instances details
Functor ForallHeaderPart Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

Annotated ForallHeaderPart Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Data a => Data (ForallHeaderPart 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) -> ForallHeaderPart a -> c (ForallHeaderPart a) #

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

toConstr :: ForallHeaderPart a -> Constr #

dataTypeOf :: ForallHeaderPart a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (ForallHeaderPart a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: ForallHeaderPart a -> () #

Spanned (ForallHeaderPart a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

FirstParameter (ForallHeaderPart a) a Source # 
Instance details

Defined in Language.Fortran.AST

SecondParameter (ForallHeaderPart a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ForallHeaderPart a) Source # 
Instance details

Defined in Language.Fortran.AST

type Rep (ForallHeaderPart a) = D1 ('MetaData "ForallHeaderPart" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "ForallHeaderPart" 'PrefixI 'True) ((S1 ('MetaSel ('Just "forallHeaderPartAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "forallHeaderPartSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Just "forallHeaderPartName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :*: (S1 ('MetaSel ('Just "forallHeaderPartStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: (S1 ('MetaSel ('Just "forallHeaderPartEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "forallHeaderPartStride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))))

data Only Source #

Constructors

Exclusive 
Permissive 

Instances

Instances details
Out Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Only -> Doc #

doc :: Only -> Doc #

docList :: [Only] -> Doc #

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 #

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 #

Show Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

showsPrec :: Int -> Only -> ShowS #

show :: Only -> String #

showList :: [Only] -> ShowS #

NFData Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: Only -> () #

Pretty Only Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Eq Only Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

type Rep Only Source # 
Instance details

Defined in Language.Fortran.AST

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

data MetaInfo Source #

Constructors

MetaInfo 

Instances

Instances details
Out MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> MetaInfo -> Doc #

doc :: MetaInfo -> Doc #

docList :: [MetaInfo] -> Doc #

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 #

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 #

Show MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

NFData MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: MetaInfo -> () #

Eq MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

type Rep MetaInfo Source # 
Instance details

Defined in Language.Fortran.AST

type Rep MetaInfo = D1 ('MetaData "MetaInfo" "Language.Fortran.AST" "fortran-src-0.15.1-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 ModuleNature Source #

Instances

Instances details
Out 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 #

Generic ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep ModuleNature :: Type -> Type #

Show ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

NFData ModuleNature Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: ModuleNature -> () #

Eq 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.15.1-inplace" 'False) (C1 ('MetaCons "ModIntrinsic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModNonIntrinsic" 'PrefixI 'False) (U1 :: Type -> Type))

data Use a Source #

Part of USE statement. (F2018 14.2.2)

Expressions may be names or operators.

Constructors

UseRename 

Fields

UseID a SrcSpan (Expression a)

name

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 #

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Use a -> () #

Pretty (Use a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Methods

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

Spanned (Use a) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getSpan :: Use a -> SrcSpan Source #

setSpan :: SrcSpan -> 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 #

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 #

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

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Argument a -> () #

Pretty (Argument a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Argument a) 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 #

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

type Rep (Argument a) = D1 ('MetaData "Argument" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "Argument" 'PrefixI 'True) ((S1 ('MetaSel ('Just "argumentAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "argumentSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "argumentName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "argumentExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ArgumentExpression a)))))

data ArgumentExpression a Source #

Extra data type to disambiguate between plain variable arguments and expression arguments (due to apparent behaviour of some Fortran compilers to treat these differently).

Note the Annotated and Spanned instances pass to the inner Expression for ArgExpr.

Instances

Instances details
Functor ArgumentExpression Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ArgumentExpression Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Data a => Data (ArgumentExpression 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) -> ArgumentExpression a -> c (ArgumentExpression a) #

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

toConstr :: ArgumentExpression a -> Constr #

dataTypeOf :: ArgumentExpression a -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (ArgumentExpression a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: ArgumentExpression a -> () #

Pretty (ArgumentExpression a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (ArgumentExpression a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

type Rep (ArgumentExpression a) Source # 
Instance details

Defined in Language.Fortran.AST

data Intent Source #

Constructors

In 
Out 
InOut 

Instances

Instances details
Out Intent Source # 
Instance details

Defined in Language.Fortran.AST

Methods

docPrec :: Int -> Intent -> Doc #

doc :: Intent -> Doc #

docList :: [Intent] -> Doc #

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 #

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 #

Show Intent Source # 
Instance details

Defined in Language.Fortran.AST

NFData Intent Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: Intent -> () #

Pretty Intent Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Eq Intent Source # 
Instance details

Defined in Language.Fortran.AST

Methods

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

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

type Rep Intent Source # 
Instance details

Defined in Language.Fortran.AST

type Rep Intent = D1 ('MetaData "Intent" "Language.Fortran.AST" "fortran-src-0.15.1-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 #

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: ControlPair a -> () #

Pretty (ControlPair a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (ControlPair a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

type Rep (ControlPair a) = D1 ('MetaData "ControlPair" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "ControlPair" 'PrefixI 'True) ((S1 ('MetaSel ('Just "controlPairAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "controlPairSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "controlPairName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "controlPairExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)))))

data AllocOpt a Source #

Constructors

AOStat

(output) status of allocation

Fields

AOErrMsg

(output) error condition if present

Fields

AOSource a SrcSpan (Expression a) 

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

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: AllocOpt a -> () #

Pretty (AllocOpt a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (AllocOpt a) 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 #

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 #

List of names for an IMPLICIT statement.

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

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: ImpList a -> () #

Pretty (ImpList a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (ImpList a) 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 #

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

type Rep (ImpList a) = D1 ('MetaData "ImpList" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "ImpList" 'PrefixI 'True) ((S1 ('MetaSel ('Just "impListAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "impListSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "impListType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeSpec a)) :*: S1 ('MetaSel ('Just "impListElements") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList ImpElement a)))))

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: ImpElement a -> () #

Pretty (ImpElement a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (ImpElement a) 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 #

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

type Rep (ImpElement a) = D1 ('MetaData "ImpElement" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "ImpElement" 'PrefixI 'True) ((S1 ('MetaSel ('Just "impElementAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "impElementSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "impElementFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Just "impElementTo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Char)))))

data CommonGroup a Source #

A single COMMON block definition.

The Declarators here shall not contain initializing expressions.

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: CommonGroup a -> () #

Pretty (CommonGroup a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (CommonGroup a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

type Rep (CommonGroup a) = D1 ('MetaData "CommonGroup" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "CommonGroup" 'PrefixI 'True) ((S1 ('MetaSel ('Just "commonGroupAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "commonGroupSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "commonGroupName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a))) :*: S1 ('MetaSel ('Just "commonGroupVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Declarator a)))))

data Namelist a Source #

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

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: Namelist a -> () #

Pretty (Namelist a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (Namelist a) 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 #

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

type Rep (Namelist a) = D1 ('MetaData "Namelist" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "Namelist" 'PrefixI 'True) ((S1 ('MetaSel ('Just "namelistAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "namelistSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "namelistName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "namelistVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))))

data DataGroup a Source #

The part of a DATA statement describing a single set of initializations.

The initializer list must be compatible with the name list. Generally, that means either the lengths must be equal, or the name list is the singleton list referring to an array, and the initializer list is compatible with that array's shape.

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: DataGroup a -> () #

Pretty (DataGroup a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (DataGroup a) 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 #

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

type Rep (DataGroup a) = D1 ('MetaData "DataGroup" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "DataGroup" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dataGroupAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "dataGroupSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "dataGroupNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)) :*: S1 ('MetaSel ('Just "dataGroupInitializers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList Expression a)))))

data StructureItem a Source #

Field types in pre-Fortran 90 non-standard structurerecordunion extension.

Structures were obsoleted by derived types in later standards.

The outer structure is stored in StStructure.

Constructors

StructFields

Regular field

Fields

StructUnion

Union field

Fields

StructStructure

Substructure (nestedinline recordstructure)

Fields

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

Out a => Out (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) #

Generic (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: StructureItem a -> () #

IndentablePretty (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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.15.1-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 #

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

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 #

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

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 #

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 #

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

Defined in Language.Fortran.AST

Methods

rnf :: UnionMap a -> () #

IndentablePretty (UnionMap a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (UnionMap a) 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 #

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

type Rep (UnionMap a) = D1 ('MetaData "UnionMap" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "UnionMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "unionMapAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "unionMapSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Just "unionMapFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AList StructureItem a)))))

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: FormatItem a -> () #

Pretty (FormatItem a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (FormatItem a) 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 #

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.15.1-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 #

Constructors

FSUnit a SrcSpan (Expression a)

scalar integer expression

FSIOStat a SrcSpan (Expression a)

scalar integer variable

FSIOMsg a SrcSpan (Expression a)

scalar character variable

FSErr a SrcSpan (Expression a)

statement label

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

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 #

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

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 #

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: FlushSpec a -> () #

Pretty (FlushSpec a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (FlushSpec a) 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 #

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.15.1-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

Out a => Out (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) #

Generic (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

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

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

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Methods

rnf :: DoSpecification a -> () #

Pretty (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Spanned (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

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

type Rep (DoSpecification a) = D1 ('MetaData "DoSpecification" "Language.Fortran.AST" "fortran-src-0.15.1-inplace" 'False) (C1 ('MetaCons "DoSpecification" 'PrefixI 'True) ((S1 ('MetaSel ('Just "doSpecAnno") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "doSpecSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "doSpecInitial") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Statement a)) :*: (S1 ('MetaSel ('Just "doSpecLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Expression a)) :*: S1 ('MetaSel ('Just "doSpecIncrement") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Expression a)))))))

data ProgramUnitName Source #

Instances

Instances details
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 #

Generic ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Associated Types

type Rep ProgramUnitName :: Type -> Type #

Show ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Binary ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

NFData ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Methods

rnf :: ProgramUnitName -> () #

Eq ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

Ord ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

type Rep ProgramUnitName Source # 
Instance details

Defined in Language.Fortran.AST

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

Node annotations & related typeclasses

type A0 = () Source #

The empty annotation.

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

Defined in Language.Fortran.AST

Annotated Argument Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ArgumentExpression Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Annotated ControlPair Source # 
Instance details

Defined in Language.Fortran.AST

Annotated DataGroup Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Declarator Source # 
Instance details

Defined in Language.Fortran.AST

Annotated DimensionDeclarator Source # 
Instance details

Defined in Language.Fortran.AST

Annotated DoSpecification Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Expression Source # 
Instance details

Defined in Language.Fortran.AST

Annotated FlushSpec Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ForallHeader Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ForallHeaderPart Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST

Annotated ProcDecl Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ProcInterface Source # 
Instance details

Defined in Language.Fortran.AST

Annotated ProgramUnit Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Selector Source # 
Instance details

Defined in Language.Fortran.AST

Annotated Statement Source # 
Instance details

Defined in Language.Fortran.AST

Annotated StructureItem Source # 
Instance details

Defined in Language.Fortran.AST

Annotated TypeSpec Source # 
Instance details

Defined in Language.Fortran.AST

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

Defined in Language.Fortran.AST.Literal

Annotated ComplexLit Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

Annotated ComplexPart Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Complex

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.AList

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 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 Named a where Source #

Instances

Instances details
Named (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.AST

Helpers

setInitialisation :: Declarator a -> Expression a -> Declarator a Source #

Set a Declarator's initializing expression only if it has none already.

Assorted getters & setters

Re-exports

data NonEmpty a #

Non-empty (and non-strict) list type.

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Instances details
MonadFix NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> NonEmpty a) -> NonEmpty a #

Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

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

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

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

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

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

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

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

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

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

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

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

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

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

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> NonEmpty a -> NonEmpty b -> Bool #

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> NonEmpty a -> NonEmpty b -> Ordering #

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NonEmpty a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NonEmpty a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NonEmpty a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NonEmpty a] #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NonEmpty a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NonEmpty a] -> ShowS #

Traversable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

NFData1 NonEmpty

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> NonEmpty a -> () #

Hashable1 NonEmpty

Since: hashable-1.3.1.0

Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> NonEmpty a -> Int #

Generic1 NonEmpty 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> Type #

Methods

from1 :: forall (a :: k). NonEmpty a -> Rep1 NonEmpty a #

to1 :: forall (a :: k). Rep1 NonEmpty a -> NonEmpty a #

Lift a => Lift (NonEmpty a :: Type)

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => NonEmpty a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NonEmpty a -> Code m (NonEmpty a) #

SingI1 ((:|@#@$$) :: a -> TyFun [a] (NonEmpty a) -> Type) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ((:|@#@$$) x) #

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

Defined in Language.Fortran.AST

Methods

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

doc :: NonEmpty a -> Doc #

docList :: [NonEmpty a] -> Doc #

Data a => Data (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: NonEmpty a -> Constr #

dataTypeOf :: NonEmpty a -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item (NonEmpty a) #

Methods

fromList :: [Item (NonEmpty a)] -> NonEmpty a #

fromListN :: Int -> [Item (NonEmpty a)] -> NonEmpty a #

toList :: NonEmpty a -> [Item (NonEmpty a)] #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Read a => Read (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Binary a => Binary (NonEmpty a)

Since: binary-0.8.4.0

Instance details

Defined in Data.Binary.Class

Methods

put :: NonEmpty a -> Put #

get :: Get (NonEmpty a) #

putList :: [NonEmpty a] -> Put #

NFData a => NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () #

Spanned a => Spanned (NonEmpty a) Source # 
Instance details

Defined in Language.Fortran.Util.Position

Eq a => Eq (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Ord a => Ord (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

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

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

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

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

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

Hashable a => Hashable (NonEmpty a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> NonEmpty a -> Int #

hash :: NonEmpty a -> Int #

PEq (NonEmpty a) 
Instance details

Defined in Data.Eq.Singletons

Associated Types

type arg == arg1 :: Bool #

type arg /= arg1 :: Bool #

(SEq a, SEq [a]) => SEq (NonEmpty a) 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (==@#@$) t1) t2) #

(%/=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (/=@#@$) t1) t2) #

POrd (NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

(SOrd a, SOrd [a]) => SOrd (NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

(SDecide a, SDecide [a]) => TestCoercion (SNonEmpty :: NonEmpty a -> Type) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: k) (b :: k). SNonEmpty a0 -> SNonEmpty b -> Maybe (Coercion a0 b) #

(SDecide a, SDecide [a]) => TestEquality (SNonEmpty :: NonEmpty a -> Type) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: k) (b :: k). SNonEmpty a0 -> SNonEmpty b -> Maybe (a0 :~: b) #

SingI ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (:|@#@$) #

SuppressUnusedWarnings (Compare_6989586621679299464Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Ordering) -> Type) 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679141588Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) 
Instance details

Defined in Data.Singletons.Base.Instances

SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:|@#@$$) d) #

SuppressUnusedWarnings (Compare_6989586621679299464Sym1 a6989586621679299469 :: TyFun (NonEmpty a) Ordering -> Type) 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679141588Sym1 a6989586621679141593 :: TyFun (NonEmpty a) Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((:|@#@$$) a6989586621679028402 :: TyFun [a] (NonEmpty a) -> Type) 
Instance details

Defined in Data.Singletons.Base.Instances

type Rep1 NonEmpty

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679028402 :: a) 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679028402 :: a) = (:|@#@$$) a6989586621679028402
type Item (NonEmpty a) 
Instance details

Defined in GHC.Exts

type Item (NonEmpty a) = a
type Rep (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Demote (NonEmpty a) 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SNonEmpty :: NonEmpty a -> Type
type (arg1 :: NonEmpty a) /= (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Eq.Singletons

type (arg1 :: NonEmpty a) /= (arg2 :: NonEmpty a) = Apply (Apply (TFHelper_6989586621679137070Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) arg1) arg2
type (a2 :: NonEmpty a1) == (a3 :: NonEmpty a1) 
Instance details

Defined in Data.Eq.Singletons

type (a2 :: NonEmpty a1) == (a3 :: NonEmpty a1) = Apply (Apply (TFHelper_6989586621679141588Sym0 :: TyFun (NonEmpty a1) (NonEmpty a1 ~> Bool) -> Type) a2) a3
type (arg1 :: NonEmpty a) < (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: NonEmpty a) < (arg2 :: NonEmpty a) = Apply (Apply (TFHelper_6989586621679284846Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) arg1) arg2
type (arg1 :: NonEmpty a) <= (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: NonEmpty a) <= (arg2 :: NonEmpty a) = Apply (Apply (TFHelper_6989586621679284862Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) arg1) arg2
type (arg1 :: NonEmpty a) > (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: NonEmpty a) > (arg2 :: NonEmpty a) = Apply (Apply (TFHelper_6989586621679284878Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) arg1) arg2
type (arg1 :: NonEmpty a) >= (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: NonEmpty a) >= (arg2 :: NonEmpty a) = Apply (Apply (TFHelper_6989586621679284894Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) arg1) arg2
type Compare (a2 :: NonEmpty a1) (a3 :: NonEmpty a1) 
Instance details

Defined in Data.Ord.Singletons

type Compare (a2 :: NonEmpty a1) (a3 :: NonEmpty a1) = Apply (Apply (Compare_6989586621679299464Sym0 :: TyFun (NonEmpty a1) (NonEmpty a1 ~> Ordering) -> Type) a2) a3
type Max (arg1 :: NonEmpty a) (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

type Max (arg1 :: NonEmpty a) (arg2 :: NonEmpty a) = Apply (Apply (Max_6989586621679284910Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> NonEmpty a) -> Type) arg1) arg2
type Min (arg1 :: NonEmpty a) (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

type Min (arg1 :: NonEmpty a) (arg2 :: NonEmpty a) = Apply (Apply (Min_6989586621679284926Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> NonEmpty a) -> Type) arg1) arg2
type Apply (Compare_6989586621679299464Sym1 a6989586621679299469 :: TyFun (NonEmpty a) Ordering -> Type) (a6989586621679299470 :: NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Compare_6989586621679299464Sym1 a6989586621679299469 :: TyFun (NonEmpty a) Ordering -> Type) (a6989586621679299470 :: NonEmpty a) = Compare_6989586621679299464 a6989586621679299469 a6989586621679299470
type Apply (TFHelper_6989586621679141588Sym1 a6989586621679141593 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621679141594 :: NonEmpty a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679141588Sym1 a6989586621679141593 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621679141594 :: NonEmpty a) = TFHelper_6989586621679141588 a6989586621679141593 a6989586621679141594
type Apply ((:|@#@$$) a6989586621679028402 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679028403 :: [a]) 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$$) a6989586621679028402 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679028403 :: [a]) = a6989586621679028402 :| a6989586621679028403
type Apply (Compare_6989586621679299464Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Ordering) -> Type) (a6989586621679299469 :: NonEmpty a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Compare_6989586621679299464Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Ordering) -> Type) (a6989586621679299469 :: NonEmpty a) = Compare_6989586621679299464Sym1 a6989586621679299469
type Apply (TFHelper_6989586621679141588Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) (a6989586621679141593 :: NonEmpty a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679141588Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) (a6989586621679141593 :: NonEmpty a) = TFHelper_6989586621679141588Sym1 a6989586621679141593

Orphan instances

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

Methods

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

doc :: NonEmpty a -> Doc #

docList :: [NonEmpty a] -> Doc #