habs-parser-0.0.1: The parser of the Haskell-ABS (habs) backend

Safe HaskellSafe
LanguageHaskell98

ABS.AST

Contents

Description

A wrapper on the BNFC-generated AST, that re-adds (custom) Eq,Ord instances after being sed-removed by make generate.

Documentation

newtype U Source #

Constructors

U ((Int, Int), String) 

Instances

Data U Source # 

Methods

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

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

toConstr :: U -> Constr #

dataTypeOf :: U -> DataType #

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

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

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

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

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

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

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

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

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

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

Read U Source # 
Show U Source # 

Methods

showsPrec :: Int -> U -> ShowS #

show :: U -> String #

showList :: [U] -> ShowS #

Generic U Source # 

Associated Types

type Rep U :: * -> * #

Methods

from :: U -> Rep U x #

to :: Rep U x -> U #

type Rep U Source # 
type Rep U = D1 (MetaData "U" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" True) (C1 (MetaCons "U" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

newtype L Source #

Constructors

L ((Int, Int), String) 

Instances

Data L Source # 

Methods

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

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

toConstr :: L -> Constr #

dataTypeOf :: L -> DataType #

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

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

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

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

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

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

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

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

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

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

Read L Source # 
Show L Source # 

Methods

showsPrec :: Int -> L -> ShowS #

show :: L -> String #

showList :: [L] -> ShowS #

Generic L Source # 

Associated Types

type Rep L :: * -> * #

Methods

from :: L -> Rep L x #

to :: Rep L x -> L #

type Rep L Source # 
type Rep L = D1 (MetaData "L" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" True) (C1 (MetaCons "L" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((Int, Int), String))))

data Literal Source #

Instances

Data Literal Source # 

Methods

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

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

toConstr :: Literal -> Constr #

dataTypeOf :: Literal -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Literal Source # 
Show Literal Source # 
Generic Literal Source # 

Associated Types

type Rep Literal :: * -> * #

Methods

from :: Literal -> Rep Literal x #

to :: Rep Literal x -> Literal #

type Rep Literal Source # 

data QU Source #

Constructors

U_ U 
QU U QU 

Instances

Data QU Source # 

Methods

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

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

toConstr :: QU -> Constr #

dataTypeOf :: QU -> DataType #

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

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

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

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

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

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

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

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

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

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

Read QU Source # 
Show QU Source # 

Methods

showsPrec :: Int -> QU -> ShowS #

show :: QU -> String #

showList :: [QU] -> ShowS #

Generic QU Source # 

Associated Types

type Rep QU :: * -> * #

Methods

from :: QU -> Rep QU x #

to :: Rep QU x -> QU #

type Rep QU Source # 

data QL Source #

Constructors

L_ L 
QL U QL 

Instances

Data QL Source # 

Methods

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

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

toConstr :: QL -> Constr #

dataTypeOf :: QL -> DataType #

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

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

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

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

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

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

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

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

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

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

Read QL Source # 
Show QL Source # 

Methods

showsPrec :: Int -> QL -> ShowS #

show :: QL -> String #

showList :: [QL] -> ShowS #

Generic QL Source # 

Associated Types

type Rep QL :: * -> * #

Methods

from :: QL -> Rep QL x #

to :: Rep QL x -> QL #

type Rep QL Source # 

data QA Source #

Constructors

LA L 
UA U 
QA U QA 

Instances

Data QA Source # 

Methods

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

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

toConstr :: QA -> Constr #

dataTypeOf :: QA -> DataType #

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

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

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

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

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

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

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

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

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

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

Read QA Source # 
Show QA Source # 

Methods

showsPrec :: Int -> QA -> ShowS #

show :: QA -> String #

showList :: [QA] -> ShowS #

Generic QA Source # 

Associated Types

type Rep QA :: * -> * #

Methods

from :: QA -> Rep QA x #

to :: Rep QA x -> QA #

type Rep QA Source # 

data T Source #

Constructors

TSimple QU 
TPoly QU [T] 
TInfer 

Instances

Data T Source # 

Methods

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

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

toConstr :: T -> Constr #

dataTypeOf :: T -> DataType #

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

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

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

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

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

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

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

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

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

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

Read T Source # 
Show T Source # 

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Generic T Source # 

Associated Types

type Rep T :: * -> * #

Methods

from :: T -> Rep T x #

to :: Rep T x -> T #

type Rep T Source # 

data FormalPar Source #

Constructors

FormalPar T L 

Instances

Data FormalPar Source # 

Methods

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

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

toConstr :: FormalPar -> Constr #

dataTypeOf :: FormalPar -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FormalPar Source # 
Show FormalPar Source # 
Generic FormalPar Source # 

Associated Types

type Rep FormalPar :: * -> * #

type Rep FormalPar Source # 
type Rep FormalPar = D1 (MetaData "FormalPar" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) (C1 (MetaCons "FormalPar" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 T)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L))))

data Program Source #

Constructors

Program [Module] 

Instances

Data Program Source # 

Methods

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

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

toConstr :: Program -> Constr #

dataTypeOf :: Program -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Program Source # 
Show Program Source # 
Generic Program Source # 

Associated Types

type Rep Program :: * -> * #

Methods

from :: Program -> Rep Program x #

to :: Rep Program x -> Program #

type Rep Program Source # 
type Rep Program = D1 (MetaData "Program" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) (C1 (MetaCons "Program" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Module])))

data Module Source #

Constructors

Module QU [Export] [Import] [AnnDecl] MaybeBlock 

Instances

Data Module Source # 

Methods

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

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

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Module Source # 
Show Module Source # 
Generic Module Source # 

Associated Types

type Rep Module :: * -> * #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

type Rep Module Source # 

data Export Source #

Instances

Data Export Source # 

Methods

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

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

toConstr :: Export -> Constr #

dataTypeOf :: Export -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Export Source # 
Show Export Source # 
Generic Export Source # 

Associated Types

type Rep Export :: * -> * #

Methods

from :: Export -> Rep Export x #

to :: Rep Export x -> Export #

type Rep Export Source # 

data Import Source #

Instances

Data Import Source # 

Methods

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

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

toConstr :: Import -> Constr #

dataTypeOf :: Import -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Import Source # 
Show Import Source # 
Generic Import Source # 

Associated Types

type Rep Import :: * -> * #

Methods

from :: Import -> Rep Import x #

to :: Rep Import x -> Import #

type Rep Import Source # 

data IsForeign Source #

Constructors

NoForeign 
YesForeign 

Instances

Data IsForeign Source # 

Methods

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

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

toConstr :: IsForeign -> Constr #

dataTypeOf :: IsForeign -> DataType #

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

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

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

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

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

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

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

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

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

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

Read IsForeign Source # 
Show IsForeign Source # 
Generic IsForeign Source # 

Associated Types

type Rep IsForeign :: * -> * #

type Rep IsForeign Source # 
type Rep IsForeign = D1 (MetaData "IsForeign" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) ((:+:) (C1 (MetaCons "NoForeign" PrefixI False) U1) (C1 (MetaCons "YesForeign" PrefixI False) U1))

data Decl Source #

Instances

Data Decl Source # 

Methods

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

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

toConstr :: Decl -> Constr #

dataTypeOf :: Decl -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Decl Source # 
Show Decl Source # 

Methods

showsPrec :: Int -> Decl -> ShowS #

show :: Decl -> String #

showList :: [Decl] -> ShowS #

Generic Decl Source # 

Associated Types

type Rep Decl :: * -> * #

Methods

from :: Decl -> Rep Decl x #

to :: Rep Decl x -> Decl #

type Rep Decl Source # 
type Rep Decl = D1 (MetaData "Decl" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "DType" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 T)))) ((:+:) (C1 (MetaCons "DTypePoly" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [U])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 T))))) (C1 (MetaCons "DData" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ConstrIdent])))))) ((:+:) (C1 (MetaCons "DDataPoly" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [U])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ConstrIdent]))))) ((:+:) (C1 (MetaCons "DFun" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 T)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FormalPar])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FunBody))))) (C1 (MetaCons "DFunPoly" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 T)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [U])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FormalPar])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FunBody))))))))) ((:+:) ((:+:) (C1 (MetaCons "DInterf" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [MethSig])))) ((:+:) (C1 (MetaCons "DExtends" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [QU])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [MethSig]))))) (C1 (MetaCons "DClass" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ClassBody]))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaybeBlock)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ClassBody]))))))) ((:+:) ((:+:) (C1 (MetaCons "DClassPar" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FormalPar]))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ClassBody])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaybeBlock)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ClassBody])))))) (C1 (MetaCons "DClassImplements" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [QU]))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ClassBody])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaybeBlock)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ClassBody]))))))) ((:+:) (C1 (MetaCons "DClassParImplements" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 U)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FormalPar])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [QU])))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ClassBody])) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaybeBlock)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ClassBody])))))) (C1 (MetaCons "DException" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ConstrIdent)))))))

data ConstrIdent Source #

Instances

Data ConstrIdent Source # 

Methods

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

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

toConstr :: ConstrIdent -> Constr #

dataTypeOf :: ConstrIdent -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ConstrIdent Source # 
Show ConstrIdent Source # 
Generic ConstrIdent Source # 

Associated Types

type Rep ConstrIdent :: * -> * #

type Rep ConstrIdent Source # 

data ConstrType Source #

Instances

Data ConstrType Source # 

Methods

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

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

toConstr :: ConstrType -> Constr #

dataTypeOf :: ConstrType -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ConstrType Source # 
Show ConstrType Source # 
Generic ConstrType Source # 

Associated Types

type Rep ConstrType :: * -> * #

type Rep ConstrType Source # 

data FunBody Source #

Instances

Data FunBody Source # 

Methods

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

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

toConstr :: FunBody -> Constr #

dataTypeOf :: FunBody -> DataType #

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

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

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

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

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

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

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

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

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

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

Read FunBody Source # 
Show FunBody Source # 
Generic FunBody Source # 

Associated Types

type Rep FunBody :: * -> * #

Methods

from :: FunBody -> Rep FunBody x #

to :: Rep FunBody x -> FunBody #

type Rep FunBody Source # 
type Rep FunBody = D1 (MetaData "FunBody" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) ((:+:) (C1 (MetaCons "BuiltinFunBody" PrefixI False) U1) (C1 (MetaCons "NormalFunBody" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))))

data MethSig Source #

Constructors

MethSig [Ann] T L [FormalPar] 

Instances

Data MethSig Source # 

Methods

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

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

toConstr :: MethSig -> Constr #

dataTypeOf :: MethSig -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MethSig Source # 
Show MethSig Source # 
Generic MethSig Source # 

Associated Types

type Rep MethSig :: * -> * #

Methods

from :: MethSig -> Rep MethSig x #

to :: Rep MethSig x -> MethSig #

type Rep MethSig Source # 

data ClassBody Source #

Instances

Data ClassBody Source # 

Methods

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

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

toConstr :: ClassBody -> Constr #

dataTypeOf :: ClassBody -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ClassBody Source # 
Show ClassBody Source # 
Generic ClassBody Source # 

Associated Types

type Rep ClassBody :: * -> * #

type Rep ClassBody Source # 

data Stm Source #

Instances

Data Stm Source # 

Methods

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

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

toConstr :: Stm -> Constr #

dataTypeOf :: Stm -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Stm Source # 
Show Stm Source # 

Methods

showsPrec :: Int -> Stm -> ShowS #

show :: Stm -> String #

showList :: [Stm] -> ShowS #

Generic Stm Source # 

Associated Types

type Rep Stm :: * -> * #

Methods

from :: Stm -> Rep Stm x #

to :: Rep Stm x -> Stm #

type Rep Stm Source # 
type Rep Stm = D1 (MetaData "Stm" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "SSkip" PrefixI False) U1) (C1 (MetaCons "SSuspend" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SReturn" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))) ((:+:) (C1 (MetaCons "SAssert" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))) (C1 (MetaCons "SAwait" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AwaitGuard)))))) ((:+:) ((:+:) (C1 (MetaCons "SAss" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))) (C1 (MetaCons "SFieldAss" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) ((:+:) (C1 (MetaCons "SDec" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 T)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)))) ((:+:) (C1 (MetaCons "SDecAss" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 T)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "SWhile" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AnnStm)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "SIf" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Stm)))) (C1 (MetaCons "SIfElse" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Stm)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Stm)))))) ((:+:) (C1 (MetaCons "SCase" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SCaseBranch])))) ((:+:) (C1 (MetaCons "SBlock" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AnnStm]))) (C1 (MetaCons "SExp" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)))))) ((:+:) ((:+:) (C1 (MetaCons "SPrint" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))) ((:+:) (C1 (MetaCons "SPrintln" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))) (C1 (MetaCons "SThrow" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))))) ((:+:) (C1 (MetaCons "STryCatchFinally" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AnnStm)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SCaseBranch])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MaybeFinally))))) ((:+:) (C1 (MetaCons "SGive" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) (C1 (MetaCons "SDuration" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))))))))

data SCaseBranch Source #

Constructors

SCaseBranch Pattern AnnStm 

Instances

Data SCaseBranch Source # 

Methods

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

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

toConstr :: SCaseBranch -> Constr #

dataTypeOf :: SCaseBranch -> DataType #

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

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

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

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

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

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

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

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

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

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

Read SCaseBranch Source # 
Show SCaseBranch Source # 
Generic SCaseBranch Source # 

Associated Types

type Rep SCaseBranch :: * -> * #

type Rep SCaseBranch Source # 
type Rep SCaseBranch = D1 (MetaData "SCaseBranch" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) (C1 (MetaCons "SCaseBranch" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pattern)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AnnStm))))

data AwaitGuard Source #

Instances

Data AwaitGuard Source # 

Methods

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

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

toConstr :: AwaitGuard -> Constr #

dataTypeOf :: AwaitGuard -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AwaitGuard Source # 
Show AwaitGuard Source # 
Generic AwaitGuard Source # 

Associated Types

type Rep AwaitGuard :: * -> * #

type Rep AwaitGuard Source # 

data Exp Source #

Constructors

ExpP PureExp 
ExpE EffExp 

Instances

Data Exp Source # 

Methods

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

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

toConstr :: Exp -> Constr #

dataTypeOf :: Exp -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Exp Source # 
Show Exp Source # 

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Generic Exp Source # 

Associated Types

type Rep Exp :: * -> * #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

type Rep Exp Source # 

data PureExp Source #

Instances

Data PureExp Source # 

Methods

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

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

toConstr :: PureExp -> Constr #

dataTypeOf :: PureExp -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PureExp Source # 
Show PureExp Source # 
Generic PureExp Source # 

Associated Types

type Rep PureExp :: * -> * #

Methods

from :: PureExp -> Rep PureExp x #

to :: Rep PureExp x -> PureExp #

type Rep PureExp Source # 
type Rep PureExp = D1 (MetaData "PureExp" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "EOr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) ((:+:) (C1 (MetaCons "EAnd" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) (C1 (MetaCons "EEq" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))))) ((:+:) (C1 (MetaCons "ENeq" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) ((:+:) (C1 (MetaCons "ELt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) (C1 (MetaCons "ELe" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))))))) ((:+:) ((:+:) (C1 (MetaCons "EGt" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) ((:+:) (C1 (MetaCons "EGe" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) (C1 (MetaCons "EAdd" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))))) ((:+:) (C1 (MetaCons "ESub" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) ((:+:) (C1 (MetaCons "EMul" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) (C1 (MetaCons "EDiv" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "EMod" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))) ((:+:) (C1 (MetaCons "ELogNeg" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))) (C1 (MetaCons "EIntNeg" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))))) ((:+:) (C1 (MetaCons "EFunCall" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QL)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp])))) ((:+:) (C1 (MetaCons "ENaryFunCall" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QL)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp])))) (C1 (MetaCons "EVar" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)))))) ((:+:) ((:+:) (C1 (MetaCons "EField" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L))) ((:+:) (C1 (MetaCons "ESinglConstr" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QU))) (C1 (MetaCons "EParamConstr" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QU)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp])))))) ((:+:) ((:+:) (C1 (MetaCons "ELit" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal))) (C1 (MetaCons "ELet" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FormalPar)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))))) ((:+:) (C1 (MetaCons "EIf" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))))) (C1 (MetaCons "ECase" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ECaseBranch])))))))))

data ECaseBranch Source #

Instances

Data ECaseBranch Source # 

Methods

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

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

toConstr :: ECaseBranch -> Constr #

dataTypeOf :: ECaseBranch -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ECaseBranch Source # 
Show ECaseBranch Source # 
Generic ECaseBranch Source # 

Associated Types

type Rep ECaseBranch :: * -> * #

type Rep ECaseBranch Source # 
type Rep ECaseBranch = D1 (MetaData "ECaseBranch" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) (C1 (MetaCons "ECaseBranch" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Pattern)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))))

data Pattern Source #

Instances

Data Pattern Source # 

Methods

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

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

toConstr :: Pattern -> Constr #

dataTypeOf :: Pattern -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Pattern Source # 
Show Pattern Source # 
Generic Pattern Source # 

Associated Types

type Rep Pattern :: * -> * #

Methods

from :: Pattern -> Rep Pattern x #

to :: Rep Pattern x -> Pattern #

type Rep Pattern Source # 

data EffExp Source #

Instances

Data EffExp Source # 

Methods

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

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

toConstr :: EffExp -> Constr #

dataTypeOf :: EffExp -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EffExp Source # 
Show EffExp Source # 
Generic EffExp Source # 

Associated Types

type Rep EffExp :: * -> * #

Methods

from :: EffExp -> Rep EffExp x #

to :: Rep EffExp x -> EffExp #

type Rep EffExp Source # 
type Rep EffExp = D1 (MetaData "EffExp" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "New" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QU)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp])))) ((:+:) (C1 (MetaCons "NewLocal" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QU)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp])))) (C1 (MetaCons "SyncMethCall" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp]))))))) ((:+:) ((:+:) (C1 (MetaCons "ThisSyncMethCall" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp])))) (C1 (MetaCons "AsyncMethCall" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp])))))) ((:+:) (C1 (MetaCons "AwaitMethCall" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 L)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PureExp]))))) (C1 (MetaCons "Get" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))))) ((:+:) ((:+:) (C1 (MetaCons "Readln" PrefixI False) U1) ((:+:) (C1 (MetaCons "ProNew" PrefixI False) U1) (C1 (MetaCons "ProTry" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp))))) ((:+:) ((:+:) (C1 (MetaCons "ThisDC" PrefixI False) U1) (C1 (MetaCons "Now" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Currentms" PrefixI False) U1) (C1 (MetaCons "Random" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PureExp)))))))

data Ann Source #

Constructors

Ann Ann_ 

Instances

Data Ann Source # 

Methods

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

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

toConstr :: Ann -> Constr #

dataTypeOf :: Ann -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Ann Source # 
Show Ann Source # 

Methods

showsPrec :: Int -> Ann -> ShowS #

show :: Ann -> String #

showList :: [Ann] -> ShowS #

Generic Ann Source # 

Associated Types

type Rep Ann :: * -> * #

Methods

from :: Ann -> Rep Ann x #

to :: Rep Ann x -> Ann #

type Rep Ann Source # 
type Rep Ann = D1 (MetaData "Ann" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) (C1 (MetaCons "Ann" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ann_)))

data Ann_ Source #

Instances

Data Ann_ Source # 

Methods

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

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

toConstr :: Ann_ -> Constr #

dataTypeOf :: Ann_ -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Ann_ Source # 
Show Ann_ Source # 

Methods

showsPrec :: Int -> Ann_ -> ShowS #

show :: Ann_ -> String #

showList :: [Ann_] -> ShowS #

Generic Ann_ Source # 

Associated Types

type Rep Ann_ :: * -> * #

Methods

from :: Ann_ -> Rep Ann_ x #

to :: Rep Ann_ x -> Ann_ #

type Rep Ann_ Source # 

data AnnStm Source #

Constructors

AnnStm [Ann] Stm 

Instances

Data AnnStm Source # 

Methods

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

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

toConstr :: AnnStm -> Constr #

dataTypeOf :: AnnStm -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnnStm Source # 
Show AnnStm Source # 
Generic AnnStm Source # 

Associated Types

type Rep AnnStm :: * -> * #

Methods

from :: AnnStm -> Rep AnnStm x #

to :: Rep AnnStm x -> AnnStm #

type Rep AnnStm Source # 
type Rep AnnStm = D1 (MetaData "AnnStm" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) (C1 (MetaCons "AnnStm" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Ann])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Stm))))

data AnnDecl Source #

Constructors

AnnDecl [Ann] Decl 

Instances

Data AnnDecl Source # 

Methods

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

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

toConstr :: AnnDecl -> Constr #

dataTypeOf :: AnnDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Read AnnDecl Source # 
Show AnnDecl Source # 
Generic AnnDecl Source # 

Associated Types

type Rep AnnDecl :: * -> * #

Methods

from :: AnnDecl -> Rep AnnDecl x #

to :: Rep AnnDecl x -> AnnDecl #

type Rep AnnDecl Source # 
type Rep AnnDecl = D1 (MetaData "AnnDecl" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) (C1 (MetaCons "AnnDecl" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Ann])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Decl))))

data MaybeFinally Source #

Instances

Data MaybeFinally Source # 

Methods

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

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

toConstr :: MaybeFinally -> Constr #

dataTypeOf :: MaybeFinally -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MaybeFinally Source # 
Show MaybeFinally Source # 
Generic MaybeFinally Source # 

Associated Types

type Rep MaybeFinally :: * -> * #

type Rep MaybeFinally Source # 
type Rep MaybeFinally = D1 (MetaData "MaybeFinally" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) ((:+:) (C1 (MetaCons "JustFinally" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AnnStm))) (C1 (MetaCons "NoFinally" PrefixI False) U1))

data MaybeBlock Source #

Constructors

JustBlock [AnnStm] 
NoBlock 

Instances

Data MaybeBlock Source # 

Methods

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

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

toConstr :: MaybeBlock -> Constr #

dataTypeOf :: MaybeBlock -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MaybeBlock Source # 
Show MaybeBlock Source # 
Generic MaybeBlock Source # 

Associated Types

type Rep MaybeBlock :: * -> * #

type Rep MaybeBlock Source # 
type Rep MaybeBlock = D1 (MetaData "MaybeBlock" "BNFC_Gen.AbsABS" "habs-parser-0.0.1-6IqcuMtNCtz7URQVDRhFuz" False) ((:+:) (C1 (MetaCons "JustBlock" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AnnStm]))) (C1 (MetaCons "NoBlock" PrefixI False) U1))

Orphan instances

Eq L Source # 

Methods

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

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

Eq U Source # 

Methods

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

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

Ord L Source # 

Methods

compare :: L -> L -> Ordering #

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

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

(>) :: L -> L -> Bool #

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

max :: L -> L -> L #

min :: L -> L -> L #

Ord U Source # 

Methods

compare :: U -> U -> Ordering #

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

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

(>) :: U -> U -> Bool #

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

max :: U -> U -> U #

min :: U -> U -> U #