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 (t a), Eq a) => Eq (AList t a) Source # | |
(Data (t a), Data 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 (t a), Show 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 # | |
Pretty (e a) => Pretty (AList e 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.2.0.0-IwNcjyoHVtfEVeYRtgdE3g" 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 # | |
Ord BaseType Source # | |
Show BaseType Source # | |
Generic BaseType Source # | |
Out BaseType Source # | |
Binary BaseType Source # | |
Pretty BaseType Source # | |
type Rep BaseType Source # | |
type Rep BaseType = D1 (MetaData "BaseType" "Language.Fortran.AST" "fortran-src-0.2.0.0-IwNcjyoHVtfEVeYRtgdE3g" 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.2.0.0-IwNcjyoHVtfEVeYRtgdE3g" False) (C1 (MetaCons "MetaInfo" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "miVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FortranVersion)) (S1 (MetaSel (Just Symbol "miFilename") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) |
data ProgramFile a Source #
pfSetFilename :: String -> ProgramFile a -> ProgramFile a Source #
pfGetFilename :: ProgramFile t -> String Source #
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] | |
PUComment a SrcSpan (Comment a) |
programUnitBody :: ProgramUnit a -> [Block a] Source #
updateProgramUnitBody :: ProgramUnit a -> [Block a] -> ProgramUnit a Source #
programUnitSubprograms :: ProgramUnit a -> Maybe [ProgramUnit a] Source #
Functor Comment Source # | |
Eq (Comment a) Source # | |
Data a => Data (Comment a) Source # | |
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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Comment a -> r # gmapQ :: (forall d. Data d => d -> u) -> Comment a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Comment a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Comment a -> m (Comment a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment a -> m (Comment a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment a -> m (Comment a) # | |
Show (Comment a) Source # | |
Generic (Comment a) Source # | |
Out a => Out (Comment a) Source # | |
type Rep (Comment a) Source # | |
BlStatement a SrcSpan (Maybe (Expression a)) (Statement a) | |
BlIf a SrcSpan (Maybe (Expression a)) (Maybe String) [Maybe (Expression a)] [[Block a]] (Maybe (Expression a)) | |
BlCase a SrcSpan (Maybe (Expression a)) (Maybe String) (Expression a) [Maybe (AList Index a)] [[Block a]] (Maybe (Expression a)) | |
BlDo a SrcSpan (Maybe (Expression a)) (Maybe String) (Maybe (Expression a)) (Maybe (DoSpecification a)) [Block a] (Maybe (Expression a)) | |
BlDoWhile a SrcSpan (Maybe (Expression a)) (Maybe String) (Expression a) [Block a] (Maybe (Expression a)) | |
BlInterface a SrcSpan (Maybe (Expression a)) [ProgramUnit a] [Block a] | |
BlComment a SrcSpan (Comment a) |
data ForallHeader a Source #
ForallHeader [(Name, Expression a, Expression a, Maybe (Expression a))] (Maybe (Expression a)) |
Eq Only Source # | |
Data Only Source # | |
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 # 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 :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Only -> r # gmapQ :: (forall d. Data d => d -> u) -> Only -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Only -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Only -> m Only # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Only -> m Only # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Only -> m Only # | |
Show Only Source # | |
Generic Only Source # | |
Out Only Source # | |
Pretty Only Source # | |
type Rep Only Source # | |
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 # | |
Pretty 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)) |
Functor Value Source # | |
Eq a => Eq (Value a) Source # | |
Data a => Data (Value a) Source # | |
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 :: (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) # | |