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

Safe HaskellNone
LanguageHaskell2010

Language.Fortran.Lexer.FixedForm

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 Token Source #

Constructors

TLeftPar SrcSpan 
TRightPar SrcSpan 
TLeftArrayPar SrcSpan 
TRightArrayPar SrcSpan 
TComma SrcSpan 
TDot SrcSpan 
TColon SrcSpan 
TInclude SrcSpan 
TProgram SrcSpan 
TFunction SrcSpan 
TSubroutine SrcSpan 
TBlockData SrcSpan 
TEnd SrcSpan 
TAssign SrcSpan 
TOpAssign SrcSpan 
TTo SrcSpan 
TGoto SrcSpan 
TIf SrcSpan 
TThen SrcSpan 
TElse SrcSpan 
TElsif SrcSpan 
TEndif SrcSpan 
TCall SrcSpan 
TReturn SrcSpan 
TSave SrcSpan 
TContinue SrcSpan 
TStop SrcSpan 
TExit SrcSpan 
TPause SrcSpan 
TDo SrcSpan 
TDoWhile SrcSpan 
TEndDo SrcSpan 
TRead SrcSpan 
TWrite SrcSpan 
TRewind SrcSpan 
TBackspace SrcSpan 
TEndfile SrcSpan 
TInquire SrcSpan 
TOpen SrcSpan 
TClose SrcSpan 
TPrint SrcSpan 
TDimension SrcSpan 
TCommon SrcSpan 
TEquivalence SrcSpan 
TExternal SrcSpan 
TIntrinsic SrcSpan 
TType SrcSpan String 
TEntry SrcSpan 
TImplicit SrcSpan 
TNone SrcSpan 
TParameter SrcSpan 
TData SrcSpan 
TFormat SrcSpan 
TFieldDescriptorDEFG SrcSpan (Maybe Integer) Char Integer Integer 
TFieldDescriptorAIL SrcSpan (Maybe Integer) Char Integer 
TBlankDescriptor SrcSpan Integer 
TScaleFactor SrcSpan Integer 
TInt SrcSpan String 
TExponent SrcSpan String 
TBool SrcSpan String 
TOpPlus SrcSpan 
TOpMinus SrcSpan 
TOpExp SrcSpan 
TStar 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 
TId SrcSpan String 
TComment SrcSpan String 
TString SrcSpan String 
THollerith SrcSpan String 
TLabel SrcSpan String 
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 #

Ord Token Source # 

Methods

compare :: Token -> Token -> Ordering #

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

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

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

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

max :: Token -> Token -> Token #

min :: Token -> Token -> 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 #

FirstParameter Token SrcSpan Source # 
LastToken AlexInput Token Source # 
type Rep Token Source # 
type Rep Token = D1 (MetaData "Token" "Language.Fortran.Lexer.FixedForm" "fortran-src-0.1.0.2-7wk5StG8EXm2GNwWT3coX7" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TLeftPar" 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 "TLeftArrayPar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) ((:+:) (C1 (MetaCons "TRightArrayPar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) (C1 (MetaCons "TComma" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)))))) ((:+:) ((:+:) (C1 (MetaCons "TDot" 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 "TInclude" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan))) ((:+:) (C1 (MetaCons "TProgram" 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 "TSubroutine" 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 "TEnd" 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 "TOpAssign" 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 "TGoto" 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 "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 "TSave" 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 "TExit" 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 "TDoWhile" 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 "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 "TRewind" 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 "TEndfile" 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 "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 "TPrint" 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 "TCommon" 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 "TExternal" 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 "TType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) (C1 (MetaCons "TEntry" 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 "TNone" 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 "TData" 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 "TFieldDescriptorDEFG" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))))) ((:+:) (C1 (MetaCons "TFieldDescriptorAIL" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))))) (C1 (MetaCons "TBlankDescriptor" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))))))) ((:+:) ((:+:) (C1 (MetaCons "TScaleFactor" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))) ((:+:) (C1 (MetaCons "TInt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) (C1 (MetaCons "TExponent" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) ((:+:) (C1 (MetaCons "TBool" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:+:) (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 "TOpExp" 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 "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 "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 "THollerith" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) ((:+:) (C1 (MetaCons "TLabel" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) ((:+:) (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))))))))))

data Move Source #

Constructors

Continuation 
Char 
Newline 

data AlexAddr Source #

Constructors

AlexA# Addr#