fortran-src-0.1.0.1: Parser and anlyses for Fortran standards 66, 77, 90.

Safe HaskellNone
LanguageHaskell2010

Language.Fortran.Lexer.FreeForm

Documentation

data AlexLastAcc a Source #

Instances

Functor AlexLastAcc Source # 

Methods

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

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

data AlexAcc a user Source #

Constructors

AlexAccNone 
AlexAcc a 
AlexAccSkip 
AlexAccPred a (AlexAccPred user) (AlexAcc a user) 
AlexAccSkipPred (AlexAccPred user) (AlexAcc a user) 

type AlexAccPred user = user -> AlexInput -> Int -> AlexInput -> Bool Source #

alexAndPred :: (t -> t1 -> t2 -> t3 -> Bool) -> (t -> t1 -> t2 -> t3 -> Bool) -> t -> t1 -> t2 -> t3 -> Bool Source #

alexPrevCharIs :: Char -> t2 -> AlexInput -> t1 -> t -> Bool Source #

alexPrevCharMatches :: (Char -> t) -> t3 -> AlexInput -> t2 -> t1 -> t Source #

alexPrevCharIsOneOf :: Array Char e -> t2 -> AlexInput -> t1 -> t -> e Source #

data Move Source #

Constructors

Continuation 
Char 
Newline 

data Token Source #

Constructors

TId SrcSpan String 
TComment SrcSpan String 
TString SrcSpan String 
TIntegerLiteral SrcSpan String 
TRealLiteral SrcSpan String 
TBozLiteral SrcSpan String 
TComma SrcSpan 
TComma2 SrcSpan 
TSemiColon SrcSpan 
TColon SrcSpan 
TDoubleColon SrcSpan 
TOpAssign SrcSpan 
TArrow SrcSpan 
TPercent SrcSpan 
TLeftPar SrcSpan 
TLeftPar2 SrcSpan 
TRightPar SrcSpan 
TLeftInitPar SrcSpan 
TRightInitPar SrcSpan 
TOpCustom SrcSpan String 
TOpExp SrcSpan 
TOpPlus SrcSpan 
TOpMinus SrcSpan 
TStar SrcSpan 
TOpDivision SrcSpan 
TSlash SrcSpan 
TOpOr SrcSpan 
TOpAnd SrcSpan 
TOpNot SrcSpan 
TOpEquivalent SrcSpan 
TOpNotEquivalent SrcSpan 
TOpLT SrcSpan 
TOpLE SrcSpan 
TOpEQ SrcSpan 
TOpNE SrcSpan 
TOpGT SrcSpan 
TOpGE SrcSpan 
TLogicalLiteral SrcSpan String 
TProgram SrcSpan 
TEndProgram SrcSpan 
TFunction SrcSpan 
TEndFunction SrcSpan 
TResult SrcSpan 
TRecursive SrcSpan 
TSubroutine SrcSpan 
TEndSubroutine SrcSpan 
TBlockData SrcSpan 
TEndBlockData SrcSpan 
TModule SrcSpan 
TEndModule SrcSpan 
TContains SrcSpan 
TUse SrcSpan 
TOnly SrcSpan 
TInterface SrcSpan 
TEndInterface SrcSpan 
TModuleProcedure SrcSpan 
TAssignment SrcSpan 
TOperator SrcSpan 
TCall SrcSpan 
TReturn SrcSpan 
TEntry SrcSpan 
TInclude SrcSpan 
TPublic SrcSpan 
TPrivate SrcSpan 
TParameter SrcSpan 
TAllocatable SrcSpan 
TDimension SrcSpan 
TExternal SrcSpan 
TIntent SrcSpan 
TIntrinsic SrcSpan 
TOptional SrcSpan 
TPointer SrcSpan 
TSave SrcSpan 
TTarget SrcSpan 
TIn SrcSpan 
TOut SrcSpan 
TInOut SrcSpan 
TData SrcSpan 
TNamelist SrcSpan 
TImplicit SrcSpan 
TEquivalence SrcSpan 
TCommon SrcSpan 
TFormat SrcSpan 
TBlob SrcSpan String 
TAllocate SrcSpan 
TDeallocate SrcSpan 
TNullify SrcSpan 
TNone SrcSpan 
TGoto SrcSpan 
TAssign SrcSpan 
TTo SrcSpan 
TContinue SrcSpan 
TStop SrcSpan 
TPause SrcSpan 
TDo SrcSpan 
TEndDo SrcSpan 
TWhile SrcSpan 
TIf SrcSpan 
TThen SrcSpan 
TElse SrcSpan 
TElsif SrcSpan 
TEndIf SrcSpan 
TCase SrcSpan 
TSelectCase SrcSpan 
TEndSelect SrcSpan 
TDefault SrcSpan 
TCycle SrcSpan 
TExit SrcSpan 
TWhere SrcSpan 
TElsewhere SrcSpan 
TEndWhere SrcSpan 
TType SrcSpan 
TEndType SrcSpan 
TSequence SrcSpan 
TKind SrcSpan 
TLen SrcSpan 
TInteger SrcSpan 
TReal SrcSpan 
TDoublePrecision SrcSpan 
TLogical SrcSpan 
TCharacter SrcSpan 
TComplex SrcSpan 
TOpen SrcSpan 
TClose SrcSpan 
TRead SrcSpan 
TWrite SrcSpan 
TPrint SrcSpan 
TBackspace SrcSpan 
TRewind SrcSpan 
TInquire SrcSpan 
TEndfile SrcSpan 
TEnd SrcSpan 
TNewline SrcSpan 
TEOF SrcSpan 

Instances

Eq Token Source # 

Methods

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

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

Data Token Source # 

Methods

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

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

toConstr :: Token -> Constr #

dataTypeOf :: Token -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Token Source # 

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 

Associated Types

type Rep Token :: * -> * #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

FirstParameter Token SrcSpan => Spanned Token Source # 
Tok Token Source # 

Methods

eofToken :: Token -> Bool Source #

SpecifiesType Token Source # 
FirstParameter Token SrcSpan Source # 
LastToken AlexInput Token Source # 
SpecifiesType [Token] Source # 

Methods

isTypeSpec :: [Token] -> Bool Source #

type Rep Token Source # 
type Rep Token = D1 (MetaData "Token" "Language.Fortran.Lexer.FreeForm" "fortran-src-0.1.0.1-9WIIAhPdlKkLkZ9dWUxyOm" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TId" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) (C1 (MetaCons "TComment" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) ((:+:) (C1 (MetaCons "TString" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) (C1 (MetaCons "TIntegerLiteral" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) ((:+:) ((:+:) (C1 (MetaCons "TRealLiteral" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) (C1 (MetaCons "TBozLiteral" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) ((:+:) (C1 (MetaCons "TComma" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TComma2" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TSemiColon" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TColon" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TDoubleColon" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpAssign" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TArrow" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TPercent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TLeftPar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TLeftPar2" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TRightPar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TLeftInitPar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TRightInitPar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpCustom" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) ((:+:) ((:+:) (C1 (MetaCons "TOpExp" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpPlus" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TOpMinus" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TStar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TOpDivision" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TSlash" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TOpOr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpAnd" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TOpNot" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpEquivalent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TOpNotEquivalent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) ((:+:) (C1 (MetaCons "TOpLT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpLE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TOpEQ" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpNE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TOpGT" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpGE" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TLogicalLiteral" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) (C1 (MetaCons "TProgram" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TEndProgram" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TFunction" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TEndFunction" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TResult" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TRecursive" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TSubroutine" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TEndSubroutine" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TBlockData" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TEndBlockData" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) ((:+:) (C1 (MetaCons "TModule" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TEndModule" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TContains" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TUse" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TOnly" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TInterface" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TEndInterface" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TModuleProcedure" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TAssignment" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOperator" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TCall" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TReturn" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TEntry" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TInclude" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TPublic" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TPrivate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TParameter" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) ((:+:) (C1 (MetaCons "TAllocatable" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TDimension" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TExternal" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TIntent" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TIntrinsic" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOptional" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TPointer" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TSave" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TTarget" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TIn" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TOut" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TInOut" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TData" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TNamelist" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TImplicit" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TEquivalence" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TCommon" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TFormat" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TBlob" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) (C1 (MetaCons "TAllocate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TDeallocate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TNullify" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TNone" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TGoto" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TAssign" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TTo" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TContinue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TStop" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TPause" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TDo" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TEndDo" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TWhile" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TIf" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) ((:+:) (C1 (MetaCons "TThen" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TElse" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TElsif" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TEndIf" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TCase" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TSelectCase" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TEndSelect" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TDefault" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TCycle" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TExit" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TWhere" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TElsewhere" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TEndWhere" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TEndType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TSequence" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TKind" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) ((:+:) (C1 (MetaCons "TLen" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TInteger" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TReal" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TDoublePrecision" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TLogical" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TCharacter" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TComplex" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TOpen" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TClose" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TRead" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TWrite" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TPrint" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TBackspace" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TRewind" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))))) ((:+:) ((:+:) (C1 (MetaCons "TInquire" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TEndfile" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))) ((:+:) (C1 (MetaCons "TEnd" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) ((:+:) (C1 (MetaCons "TNewline" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TEOF" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))))))))

class SpecifiesType a where Source #

Minimal complete definition

isTypeSpec

Methods

isTypeSpec :: a -> Bool Source #

data AlexAddr Source #

Constructors

AlexA# Addr#