Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
Functor t => Functor (AList t) Source # | |
Annotated (AList t) Source # | |
getAnnotation :: AList t a -> a Source # setAnnotation :: a -> AList t a -> AList t a Source # modifyAnnotation :: (a -> a) -> AList t a -> AList t a Source # | |
(Eq a, Eq (t a)) => Eq (AList t a) Source # | |
(Data a, Data (t a), Typeable (* -> *) t) => Data (AList t a) Source # | |
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AList t a -> c (AList t a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AList t a) # toConstr :: AList t a -> Constr # dataTypeOf :: AList t a -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (AList t a)) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AList t a)) # gmapT :: (forall b. Data b => b -> b) -> AList t a -> AList t a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AList t a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AList t a -> r # gmapQ :: (forall d. Data d => d -> u) -> AList t a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AList t a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AList t a -> m (AList t a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AList t a -> m (AList t a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AList t a -> m (AList t a) # | |
(Show a, Show (t a)) => Show (AList t a) Source # | |
Generic (AList t a) Source # | |
(Out a, Out (t a)) => Out (AList t a) Source # | |
Spanned (AList t a) Source # | |
SecondParameter (AList t a) SrcSpan Source # | |
FirstParameter (AList t a) a Source # | |
getFirstParameter :: AList t a -> a Source # setFirstParameter :: a -> AList t a -> AList t a Source # | |
type Rep (AList t a) Source # | |
type Rep (AList t a) = D1 (MetaData "AList" "Language.Fortran.AST" "fortran-src-0.1.0.2-7wk5StG8EXm2GNwWT3coX7" False) (C1 (MetaCons "AList" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [t a]))))) |
fromReverseList :: Spanned (t ()) => [t ()] -> AList t () Source #
TypeInteger | |
TypeReal | |
TypeDoublePrecision | |
TypeComplex | |
TypeDoubleComplex | |
TypeLogical | |
TypeCharacter | |
TypeCustom String |
Eq BaseType Source # | |
Data BaseType Source # | |
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 :: (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 # | |
Show BaseType Source # | |
Generic BaseType Source # | |
Out BaseType Source # | |
type Rep BaseType Source # | |
type Rep BaseType = D1 (MetaData "BaseType" "Language.Fortran.AST" "fortran-src-0.1.0.2-7wk5StG8EXm2GNwWT3coX7" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TypeInteger" PrefixI False) U1) (C1 (MetaCons "TypeReal" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TypeDoublePrecision" PrefixI False) U1) (C1 (MetaCons "TypeComplex" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "TypeDoubleComplex" PrefixI False) U1) (C1 (MetaCons "TypeLogical" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TypeCharacter" PrefixI False) U1) (C1 (MetaCons "TypeCustom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) |
Selector a SrcSpan (Maybe (Expression a)) (Maybe (Expression a)) |
Eq MetaInfo Source # | |
Data MetaInfo Source # | |
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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MetaInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> MetaInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MetaInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MetaInfo -> m MetaInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MetaInfo -> m MetaInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MetaInfo -> m MetaInfo # | |
Show MetaInfo Source # | |
Generic MetaInfo Source # | |
Out MetaInfo Source # | |
type Rep MetaInfo Source # | |
type Rep MetaInfo = D1 (MetaData "MetaInfo" "Language.Fortran.AST" "fortran-src-0.1.0.2-7wk5StG8EXm2GNwWT3coX7" False) (C1 (MetaCons "MetaInfo" PrefixI True) (S1 (MetaSel (Just Symbol "miVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FortranVersion))) |
data ProgramFile a Source #
ProgramFile MetaInfo [([Block a], ProgramUnit a)] [Block a] |
data ProgramUnit a Source #
PUMain a SrcSpan (Maybe Name) [Block a] (Maybe [ProgramUnit a]) | |
PUModule a SrcSpan Name [Block a] (Maybe [ProgramUnit a]) | |
PUSubroutine a SrcSpan Bool Name (Maybe (AList Expression a)) [Block a] (Maybe [ProgramUnit a]) | |
PUFunction a SrcSpan (Maybe (TypeSpec a)) Bool Name (Maybe (AList Expression a)) (Maybe (Expression a)) [Block a] (Maybe [ProgramUnit a]) | |
PUBlockData a SrcSpan (Maybe Name) [Block a] |
BlStatement a SrcSpan (Maybe (Expression a)) (Statement a) | |
BlIf a SrcSpan (Maybe (Expression a)) [Maybe (Expression a)] [[Block a]] | |
BlCase a SrcSpan (Maybe (Expression a)) (Expression a) [Maybe (AList Index a)] [[Block a]] | |
BlDo a SrcSpan (Maybe (Expression a)) (Maybe (DoSpecification a)) [Block a] | |
BlDoWhile a SrcSpan (Maybe (Expression a)) (Expression a) [Block a] | |
BlInterface a SrcSpan (Maybe (Expression a)) [ProgramUnit a] [Block a] | |
BlComment a SrcSpan String |
UseRename a SrcSpan (Expression a) (Expression a) | |
UseID a SrcSpan (Expression a) |
Argument a SrcSpan (Maybe String) (Expression a) |
Eq Intent Source # | |
Data Intent Source # | |
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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Intent -> r # gmapQ :: (forall d. Data d => d -> u) -> Intent -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Intent -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Intent -> m Intent # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Intent -> m Intent # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Intent -> m Intent # | |
Show Intent Source # | |
Generic Intent Source # | |
Out Intent Source # | |
type Rep Intent Source # | |
data ControlPair a Source #
ControlPair a SrcSpan (Maybe String) (Expression a) |
ImpList a SrcSpan (TypeSpec a) (AList ImpElement a) |
data ImpElement a Source #
data CommonGroup a Source #
CommonGroup a SrcSpan (Maybe (Expression a)) (AList Expression a) |
Namelist a SrcSpan (Expression a) (AList Expression a) |
DataGroup a SrcSpan (AList Expression a) (AList Expression a) |
data FormatItem a Source #
data DoSpecification a Source #
DoSpecification a SrcSpan (Statement a) (Expression a) (Maybe (Expression a)) |
data Expression a Source #
ExpValue a SrcSpan (Value a) | |
ExpBinary a SrcSpan BinaryOp (Expression a) (Expression a) | |
ExpUnary a SrcSpan UnaryOp (Expression a) | |
ExpSubscript a SrcSpan (Expression a) (AList Index a) | |
ExpDataRef a SrcSpan (Expression a) (Expression a) | |
ExpFunctionCall a SrcSpan (Expression a) (Maybe (AList Argument a)) | |
ExpImpliedDo a SrcSpan (AList Expression a) (DoSpecification a) | |
ExpInitialisation a SrcSpan (AList Expression a) | |
ExpReturnSpec a SrcSpan (Expression a) |
IxSingle a SrcSpan (Maybe String) (Expression a) | |
IxRange a SrcSpan (Maybe (Expression a)) (Maybe (Expression a)) (Maybe (Expression a)) |
data Declarator a Source #
DeclVariable a SrcSpan (Expression a) (Maybe (Expression a)) (Maybe (Expression a)) | |
DeclArray a SrcSpan (Expression a) (AList DimensionDeclarator a) (Maybe (Expression a)) (Maybe (Expression a)) |
setInitialisation :: Declarator a -> Expression a -> Declarator a Source #
data DimensionDeclarator a Source #
DimensionDeclarator a SrcSpan (Maybe (Expression a)) (Maybe (Expression a)) |
Eq UnaryOp Source # | |
Data UnaryOp Source # | |
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 :: (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 # | |
Show UnaryOp Source # | |
Generic UnaryOp Source # | |
Out UnaryOp Source # | |
type Rep UnaryOp Source # | |
type Rep UnaryOp = D1 (MetaData "UnaryOp" "Language.Fortran.AST" "fortran-src-0.1.0.2-7wk5StG8EXm2GNwWT3coX7" False) ((:+:) ((:+:) (C1 (MetaCons "Plus" PrefixI False) U1) (C1 (MetaCons "Minus" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Not" PrefixI False) U1) (C1 (MetaCons "UnCustom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) |
Addition | |
Subtraction | |
Multiplication | |
Division | |
Exponentiation | |
Concatenation | |
GT | |
GTE | |
LT | |
LTE | |
EQ | |
NE | |
Or | |
And | |
Equivalent | |
NotEquivalent | |
BinCustom String |
Eq BinaryOp Source # | |
Data BinaryOp Source # | |
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 :: (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 # | |
Show BinaryOp Source # | |
Generic BinaryOp Source # | |
Out BinaryOp Source # | |
type Rep BinaryOp Source # | |
type Rep BinaryOp = D1 (MetaData "BinaryOp" "Language.Fortran.AST" "fortran-src-0.1.0.2-7wk5StG8EXm2GNwWT3coX7" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Addition" PrefixI False) U1) (C1 (MetaCons "Subtraction" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Multiplication" PrefixI False) U1) (C1 (MetaCons "Division" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Exponentiation" PrefixI False) U1) (C1 (MetaCons "Concatenation" PrefixI False) U1)) ((:+:) (C1 (MetaCons "GT" PrefixI False) U1) (C1 (MetaCons "GTE" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "LT" PrefixI False) U1) (C1 (MetaCons "LTE" PrefixI False) U1)) ((:+:) (C1 (MetaCons "EQ" PrefixI False) U1) (C1 (MetaCons "NE" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Or" PrefixI False) U1) (C1 (MetaCons "And" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Equivalent" PrefixI False) U1) ((:+:) (C1 (MetaCons "NotEquivalent" PrefixI False) U1) (C1 (MetaCons "BinCustom" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))))) |
class Annotated f where Source #
getAnnotation :: f a -> a Source #
setAnnotation :: a -> f a -> f a Source #
modifyAnnotation :: (a -> a) -> f a -> f a Source #
getAnnotation :: FirstParameter (f a) a => f a -> a Source #
setAnnotation :: FirstParameter (f a) a => a -> f a -> f a Source #
class Labeled f where Source #
getLabel :: f a -> Maybe (Expression a) Source #
setLabel :: f a -> Expression a -> f a Source #
class Conditioned f where Source #
getCondition :: f a -> Maybe (Expression a) Source #
Conditioned Statement Source # | |
getCondition :: Statement a -> Maybe (Expression a) Source # | |
Conditioned Block Source # | |
getCondition :: Block a -> Maybe (Expression a) Source # |
data ProgramUnitName Source #
getName :: a -> ProgramUnitName Source #
setName :: ProgramUnitName -> a -> a Source #
Named (ProgramUnit a) Source # | |
getName :: ProgramUnit a -> ProgramUnitName Source # setName :: ProgramUnitName -> ProgramUnit a -> ProgramUnit a Source # |
Orphan instances
Out FortranVersion Source # | |
docPrec :: Int -> FortranVersion -> Doc # doc :: FortranVersion -> Doc # docList :: [FortranVersion] -> Doc # | |
Spanned a => Spanned [a] Source # | |
(Spanned a, Spanned b) => Spanned (Maybe a, b) Source # | |
(Spanned a, Spanned b) => Spanned (a, b) Source # | |
(Spanned a, Spanned b) => Spanned (a, Maybe b) Source # | |
(Spanned a, Spanned b, Spanned c) => Spanned (Maybe a, b, c) Source # | |
(Spanned a, Spanned b, Spanned c) => Spanned (Maybe a, Maybe b, Maybe c) Source # | |
(Spanned a, Spanned b, Spanned c) => Spanned (a, b, c) Source # | |
(Spanned a, Spanned b, Spanned c) => Spanned (a, Maybe b, Maybe c) Source # | |