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

Language.Fortran.AST.AList

Synopsis

Documentation

data AList t a Source #

A location-tagged list of t as (t decorated with an a annotation).

The AST is polymorphic on some type a, which is used for arbitrary annotations. Since many AST nodes use lists (e.g. executable statements, declarations), we define a dedicated annotated list type to reuse.

Note that the list itself also holds an a annotation.

Constructors

AList a SrcSpan [t a] 

Instances

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

Defined in Language.Fortran.AST.AList

Methods

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

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

Annotated (AList t) Source # 
Instance details

Defined in Language.Fortran.AST

Methods

getAnnotation :: AList t a -> a Source #

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

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

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

Defined in Language.Fortran.AST.AList

Methods

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

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

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

Defined in Language.Fortran.AST.AList

Methods

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

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

toConstr :: AList t a -> Constr #

dataTypeOf :: AList t a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Language.Fortran.AST.AList

Methods

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

show :: AList t a -> String #

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

Generic (AList t a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Associated Types

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

Methods

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

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

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

Defined in Language.Fortran.AST.AList

Methods

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

doc :: AList t a -> Doc #

docList :: [AList t a] -> Doc #

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

Defined in Language.Fortran.AST.AList

Methods

rnf :: AList t a -> () #

Spanned (AList t a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

getSpan :: AList t a -> SrcSpan Source #

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

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

Defined in Language.Fortran.PrettyPrint

Methods

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

FirstParameter (AList t a) a Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

getFirstParameter :: AList t a -> a Source #

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

SecondParameter (AList t a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST.AList

type Rep (AList t a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

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

Convert a non-empty list to an AList.

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

Convert a list to an AList, returning Nothing iff the list is empty.

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

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

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

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

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

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

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

data ATuple t1 t2 a Source #

Constructors

ATuple a SrcSpan (t1 a) (t2 a) 

Instances

Instances details
(Functor t1, Functor t2) => Functor (ATuple t1 t2) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

fmap :: (a -> b) -> ATuple t1 t2 a -> ATuple t1 t2 b #

(<$) :: a -> ATuple t1 t2 b -> ATuple t1 t2 a #

(Eq a, Eq (t1 a), Eq (t2 a)) => Eq (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

(==) :: ATuple t1 t2 a -> ATuple t1 t2 a -> Bool #

(/=) :: ATuple t1 t2 a -> ATuple t1 t2 a -> Bool #

(Typeable t1, Typeable t2, Data a, Data (t1 a), Data (t2 a)) => Data (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

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

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

toConstr :: ATuple t1 t2 a -> Constr #

dataTypeOf :: ATuple t1 t2 a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ATuple t1 t2 a -> ATuple t1 t2 a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ATuple t1 t2 a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ATuple t1 t2 a -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> ATuple t1 t2 a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ATuple t1 t2 a -> m (ATuple t1 t2 a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ATuple t1 t2 a -> m (ATuple t1 t2 a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ATuple t1 t2 a -> m (ATuple t1 t2 a) #

(Show a, Show (t1 a), Show (t2 a)) => Show (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

showsPrec :: Int -> ATuple t1 t2 a -> ShowS #

show :: ATuple t1 t2 a -> String #

showList :: [ATuple t1 t2 a] -> ShowS #

Generic (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Associated Types

type Rep (ATuple t1 t2 a) :: Type -> Type #

Methods

from :: ATuple t1 t2 a -> Rep (ATuple t1 t2 a) x #

to :: Rep (ATuple t1 t2 a) x -> ATuple t1 t2 a #

(Out a, Out (t1 a), Out (t2 a)) => Out (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

docPrec :: Int -> ATuple t1 t2 a -> Doc #

doc :: ATuple t1 t2 a -> Doc #

docList :: [ATuple t1 t2 a] -> Doc #

(NFData a, NFData (t1 a), NFData (t2 a)) => NFData (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

rnf :: ATuple t1 t2 a -> () #

Spanned (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

getSpan :: ATuple t1 t2 a -> SrcSpan Source #

setSpan :: SrcSpan -> ATuple t1 t2 a -> ATuple t1 t2 a Source #

(Pretty (t1 a), Pretty (t2 a)) => Pretty (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Methods

pprint' :: FortranVersion -> ATuple t1 t2 a -> Doc Source #

FirstParameter (ATuple t1 t2 a) a Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

getFirstParameter :: ATuple t1 t2 a -> a Source #

setFirstParameter :: a -> ATuple t1 t2 a -> ATuple t1 t2 a Source #

SecondParameter (ATuple t1 t2 a) SrcSpan Source # 
Instance details

Defined in Language.Fortran.AST.AList

Methods

getSecondParameter :: ATuple t1 t2 a -> SrcSpan Source #

setSecondParameter :: SrcSpan -> ATuple t1 t2 a -> ATuple t1 t2 a Source #

type Rep (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.AST.AList