ghc-8.8.1: The GHC API
Safe HaskellNone
LanguageHaskell2010

HsExtension

Synopsis

Documentation

data NoExt Source #

used as place holder in TTG values

Constructors

NoExt 

Instances

Instances details
Eq NoExt # 
Instance details

Defined in HsExtension

Methods

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

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

Data NoExt # 
Instance details

Defined in HsExtension

Methods

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

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

toConstr :: NoExt -> Constr Source #

dataTypeOf :: NoExt -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord NoExt # 
Instance details

Defined in HsExtension

Methods

compare :: NoExt -> NoExt -> Ordering #

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

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

(>) :: NoExt -> NoExt -> Bool #

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

max :: NoExt -> NoExt -> NoExt #

min :: NoExt -> NoExt -> NoExt #

Outputable NoExt # 
Instance details

Defined in HsExtension

noExt :: NoExt Source #

Used when constructing a term with an unused extension point.

data GhcPass (c :: Pass) Source #

Used as a data type index for the hsSyn AST

Instances

Instances details
Eq (GhcPass c) # 
Instance details

Defined in HsExtension

Methods

(==) :: GhcPass c -> GhcPass c -> Bool #

(/=) :: GhcPass c -> GhcPass c -> Bool #

Eq (IE GhcTc) # 
Instance details

Defined in HsInstances

Methods

(==) :: IE GhcTc -> IE GhcTc -> Bool #

(/=) :: IE GhcTc -> IE GhcTc -> Bool #

Eq (IE GhcRn) # 
Instance details

Defined in HsInstances

Methods

(==) :: IE GhcRn -> IE GhcRn -> Bool #

(/=) :: IE GhcRn -> IE GhcRn -> Bool #

Eq (IE GhcPs) # 
Instance details

Defined in HsInstances

Methods

(==) :: IE GhcPs -> IE GhcPs -> Bool #

(/=) :: IE GhcPs -> IE GhcPs -> Bool #

Typeable c => Data (GhcPass c) # 
Instance details

Defined in HsExtension

Methods

gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> GhcPass c -> c0 (GhcPass c) Source #

gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (GhcPass c) Source #

toConstr :: GhcPass c -> Constr Source #

dataTypeOf :: GhcPass c -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (GhcPass c)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (GhcPass c)) Source #

gmapT :: (forall b. Data b => b -> b) -> GhcPass c -> GhcPass c Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GhcPass c -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GhcPass c -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GhcPass c -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GhcPass c -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GhcPass c -> m (GhcPass c) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GhcPass c -> m (GhcPass c) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GhcPass c -> m (GhcPass c) Source #

Data (Pat GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcTc -> c (Pat GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcTc) Source #

toConstr :: Pat GhcTc -> Constr Source #

dataTypeOf :: Pat GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> Pat GhcTc -> Pat GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Pat GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source #

Data (Pat GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcRn -> c (Pat GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcRn) Source #

toConstr :: Pat GhcRn -> Constr Source #

dataTypeOf :: Pat GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> Pat GhcRn -> Pat GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Pat GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source #

Data (Pat GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcPs -> c (Pat GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcPs) Source #

toConstr :: Pat GhcPs -> Constr Source #

dataTypeOf :: Pat GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> Pat GhcPs -> Pat GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Pat GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source #

Data (IE GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcTc -> c (IE GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcTc) Source #

toConstr :: IE GhcTc -> Constr Source #

dataTypeOf :: IE GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcTc -> IE GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

Data (IE GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcRn -> c (IE GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcRn) Source #

toConstr :: IE GhcRn -> Constr Source #

dataTypeOf :: IE GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcRn -> IE GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

Data (IE GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcPs -> c (IE GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcPs) Source #

toConstr :: IE GhcPs -> Constr Source #

dataTypeOf :: IE GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcPs -> IE GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

Data (ImportDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcTc -> c (ImportDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcTc) Source #

toConstr :: ImportDecl GhcTc -> Constr Source #

dataTypeOf :: ImportDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcTc -> ImportDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

Data (ImportDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcRn -> c (ImportDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcRn) Source #

toConstr :: ImportDecl GhcRn -> Constr Source #

dataTypeOf :: ImportDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcRn -> ImportDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

Data (ImportDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcPs -> c (ImportDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcPs) Source #

toConstr :: ImportDecl GhcPs -> Constr Source #

dataTypeOf :: ImportDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcPs -> ImportDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

Data (SyntaxExpr GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SyntaxExpr GhcTc -> c (SyntaxExpr GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SyntaxExpr GhcTc) Source #

toConstr :: SyntaxExpr GhcTc -> Constr Source #

dataTypeOf :: SyntaxExpr GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SyntaxExpr GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SyntaxExpr GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> SyntaxExpr GhcTc -> SyntaxExpr GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExpr GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExpr GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SyntaxExpr GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SyntaxExpr GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcTc -> m (SyntaxExpr GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcTc -> m (SyntaxExpr GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcTc -> m (SyntaxExpr GhcTc) Source #

Data (SyntaxExpr GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SyntaxExpr GhcRn -> c (SyntaxExpr GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SyntaxExpr GhcRn) Source #

toConstr :: SyntaxExpr GhcRn -> Constr Source #

dataTypeOf :: SyntaxExpr GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SyntaxExpr GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SyntaxExpr GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> SyntaxExpr GhcRn -> SyntaxExpr GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExpr GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExpr GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SyntaxExpr GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SyntaxExpr GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcRn -> m (SyntaxExpr GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcRn -> m (SyntaxExpr GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcRn -> m (SyntaxExpr GhcRn) Source #

Data (SyntaxExpr GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SyntaxExpr GhcPs -> c (SyntaxExpr GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SyntaxExpr GhcPs) Source #

toConstr :: SyntaxExpr GhcPs -> Constr Source #

dataTypeOf :: SyntaxExpr GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SyntaxExpr GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SyntaxExpr GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> SyntaxExpr GhcPs -> SyntaxExpr GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExpr GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SyntaxExpr GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SyntaxExpr GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SyntaxExpr GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcPs -> m (SyntaxExpr GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcPs -> m (SyntaxExpr GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SyntaxExpr GhcPs -> m (SyntaxExpr GhcPs) Source #

Data (HsSplice GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcTc -> c (HsSplice GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcTc) Source #

toConstr :: HsSplice GhcTc -> Constr Source #

dataTypeOf :: HsSplice GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcTc -> HsSplice GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) Source #

Data (HsSplice GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcRn -> c (HsSplice GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcRn) Source #

toConstr :: HsSplice GhcRn -> Constr Source #

dataTypeOf :: HsSplice GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcRn -> HsSplice GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) Source #

Data (HsSplice GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcPs -> c (HsSplice GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcPs) Source #

toConstr :: HsSplice GhcPs -> Constr Source #

dataTypeOf :: HsSplice GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcPs -> HsSplice GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) Source #

Data (HsCmd GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcTc -> c (HsCmd GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcTc) Source #

toConstr :: HsCmd GhcTc -> Constr Source #

dataTypeOf :: HsCmd GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcTc -> HsCmd GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source #

Data (HsCmd GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcRn -> c (HsCmd GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcRn) Source #

toConstr :: HsCmd GhcRn -> Constr Source #

dataTypeOf :: HsCmd GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcRn -> HsCmd GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source #

Data (HsCmd GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcPs -> c (HsCmd GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcPs) Source #

toConstr :: HsCmd GhcPs -> Constr Source #

dataTypeOf :: HsCmd GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcPs -> HsCmd GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source #

Data (HsExpr GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcTc -> c (HsExpr GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcTc) Source #

toConstr :: HsExpr GhcTc -> Constr Source #

dataTypeOf :: HsExpr GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcTc -> HsExpr GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source #

Data (HsExpr GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcRn -> c (HsExpr GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcRn) Source #

toConstr :: HsExpr GhcRn -> Constr Source #

dataTypeOf :: HsExpr GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcRn -> HsExpr GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source #

Data (HsExpr GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcPs -> c (HsExpr GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcPs) Source #

toConstr :: HsExpr GhcPs -> Constr Source #

dataTypeOf :: HsExpr GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcPs -> HsExpr GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source #

Data (HsOverLit GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcTc -> c (HsOverLit GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcTc) Source #

toConstr :: HsOverLit GhcTc -> Constr Source #

dataTypeOf :: HsOverLit GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcTc -> HsOverLit GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source #

Data (HsOverLit GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcRn -> c (HsOverLit GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcRn) Source #

toConstr :: HsOverLit GhcRn -> Constr Source #

dataTypeOf :: HsOverLit GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcRn -> HsOverLit GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source #

Data (HsOverLit GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcPs -> c (HsOverLit GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcPs) Source #

toConstr :: HsOverLit GhcPs -> Constr Source #

dataTypeOf :: HsOverLit GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcPs -> HsOverLit GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source #

Data (HsLit GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcTc -> c (HsLit GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcTc) Source #

toConstr :: HsLit GhcTc -> Constr Source #

dataTypeOf :: HsLit GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLit GhcTc -> HsLit GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source #

Data (HsLit GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcRn -> c (HsLit GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcRn) Source #

toConstr :: HsLit GhcRn -> Constr Source #

dataTypeOf :: HsLit GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLit GhcRn -> HsLit GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source #

Data (HsLit GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcPs -> c (HsLit GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcPs) Source #

toConstr :: HsLit GhcPs -> Constr Source #

dataTypeOf :: HsLit GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLit GhcPs -> HsLit GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source #

Data (AmbiguousFieldOcc GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcTc -> c (AmbiguousFieldOcc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcTc) Source #

toConstr :: AmbiguousFieldOcc GhcTc -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcTc -> AmbiguousFieldOcc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source #

Data (AmbiguousFieldOcc GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcRn -> c (AmbiguousFieldOcc GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcRn) Source #

toConstr :: AmbiguousFieldOcc GhcRn -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcRn -> AmbiguousFieldOcc GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source #

Data (AmbiguousFieldOcc GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcPs -> c (AmbiguousFieldOcc GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcPs) Source #

toConstr :: AmbiguousFieldOcc GhcPs -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcPs -> AmbiguousFieldOcc GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source #

Data (FieldOcc GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcTc -> c (FieldOcc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcTc) Source #

toConstr :: FieldOcc GhcTc -> Constr Source #

dataTypeOf :: FieldOcc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcTc -> FieldOcc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source #

Data (FieldOcc GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcRn -> c (FieldOcc GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcRn) Source #

toConstr :: FieldOcc GhcRn -> Constr Source #

dataTypeOf :: FieldOcc GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcRn -> FieldOcc GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source #

Data (FieldOcc GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcPs -> c (FieldOcc GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcPs) Source #

toConstr :: FieldOcc GhcPs -> Constr Source #

dataTypeOf :: FieldOcc GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcPs -> FieldOcc GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source #

Data (ConDeclField GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcTc -> c (ConDeclField GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcTc) Source #

toConstr :: ConDeclField GhcTc -> Constr Source #

dataTypeOf :: ConDeclField GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcTc -> ConDeclField GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source #

Data (ConDeclField GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcRn -> c (ConDeclField GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcRn) Source #

toConstr :: ConDeclField GhcRn -> Constr Source #

dataTypeOf :: ConDeclField GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcRn -> ConDeclField GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source #

Data (ConDeclField GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcPs -> c (ConDeclField GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcPs) Source #

toConstr :: ConDeclField GhcPs -> Constr Source #

dataTypeOf :: ConDeclField GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcPs -> ConDeclField GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source #

Data (HsType GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcTc -> c (HsType GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcTc) Source #

toConstr :: HsType GhcTc -> Constr Source #

dataTypeOf :: HsType GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsType GhcTc -> HsType GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source #

Data (HsType GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcRn -> c (HsType GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcRn) Source #

toConstr :: HsType GhcRn -> Constr Source #

dataTypeOf :: HsType GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsType GhcRn -> HsType GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source #

Data (HsType GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcPs -> c (HsType GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcPs) Source #

toConstr :: HsType GhcPs -> Constr Source #

dataTypeOf :: HsType GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsType GhcPs -> HsType GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source #

Data (HsTyVarBndr GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr GhcTc -> c (HsTyVarBndr GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr GhcTc) Source #

toConstr :: HsTyVarBndr GhcTc -> Constr Source #

dataTypeOf :: HsTyVarBndr GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr GhcTc -> HsTyVarBndr GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcTc -> m (HsTyVarBndr GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcTc -> m (HsTyVarBndr GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcTc -> m (HsTyVarBndr GhcTc) Source #

Data (HsTyVarBndr GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr GhcRn -> c (HsTyVarBndr GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr GhcRn) Source #

toConstr :: HsTyVarBndr GhcRn -> Constr Source #

dataTypeOf :: HsTyVarBndr GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr GhcRn -> HsTyVarBndr GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcRn -> m (HsTyVarBndr GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcRn -> m (HsTyVarBndr GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcRn -> m (HsTyVarBndr GhcRn) Source #

Data (HsTyVarBndr GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr GhcPs -> c (HsTyVarBndr GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr GhcPs) Source #

toConstr :: HsTyVarBndr GhcPs -> Constr Source #

dataTypeOf :: HsTyVarBndr GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr GhcPs -> HsTyVarBndr GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcPs -> m (HsTyVarBndr GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcPs -> m (HsTyVarBndr GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr GhcPs -> m (HsTyVarBndr GhcPs) Source #

Data (LHsQTyVars GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcTc -> c (LHsQTyVars GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcTc) Source #

toConstr :: LHsQTyVars GhcTc -> Constr Source #

dataTypeOf :: LHsQTyVars GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcTc -> LHsQTyVars GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source #

Data (LHsQTyVars GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcRn -> c (LHsQTyVars GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcRn) Source #

toConstr :: LHsQTyVars GhcRn -> Constr Source #

dataTypeOf :: LHsQTyVars GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcRn -> LHsQTyVars GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source #

Data (LHsQTyVars GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcPs -> c (LHsQTyVars GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcPs) Source #

toConstr :: LHsQTyVars GhcPs -> Constr Source #

dataTypeOf :: LHsQTyVars GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcPs -> LHsQTyVars GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source #

Data (HsPatSynDir GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSynDir GhcTc -> c (HsPatSynDir GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcTc) Source #

toConstr :: HsPatSynDir GhcTc -> Constr Source #

dataTypeOf :: HsPatSynDir GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcTc -> HsPatSynDir GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) Source #

Data (HsPatSynDir GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSynDir GhcRn -> c (HsPatSynDir GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcRn) Source #

toConstr :: HsPatSynDir GhcRn -> Constr Source #

dataTypeOf :: HsPatSynDir GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcRn -> HsPatSynDir GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) Source #

Data (HsPatSynDir GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSynDir GhcPs -> c (HsPatSynDir GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcPs) Source #

toConstr :: HsPatSynDir GhcPs -> Constr Source #

dataTypeOf :: HsPatSynDir GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcPs -> HsPatSynDir GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) Source #

Data (FixitySig GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixitySig GhcTc -> c (FixitySig GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcTc) Source #

toConstr :: FixitySig GhcTc -> Constr Source #

dataTypeOf :: FixitySig GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcTc -> FixitySig GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) Source #

Data (FixitySig GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixitySig GhcRn -> c (FixitySig GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcRn) Source #

toConstr :: FixitySig GhcRn -> Constr Source #

dataTypeOf :: FixitySig GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcRn -> FixitySig GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) Source #

Data (FixitySig GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixitySig GhcPs -> c (FixitySig GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcPs) Source #

toConstr :: FixitySig GhcPs -> Constr Source #

dataTypeOf :: FixitySig GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcPs -> FixitySig GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) Source #

Data (Sig GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sig GhcTc -> c (Sig GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcTc) Source #

toConstr :: Sig GhcTc -> Constr Source #

dataTypeOf :: Sig GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> Sig GhcTc -> Sig GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Sig GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) Source #

Data (Sig GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sig GhcRn -> c (Sig GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcRn) Source #

toConstr :: Sig GhcRn -> Constr Source #

dataTypeOf :: Sig GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> Sig GhcRn -> Sig GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Sig GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) Source #

Data (Sig GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sig GhcPs -> c (Sig GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcPs) Source #

toConstr :: Sig GhcPs -> Constr Source #

dataTypeOf :: Sig GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> Sig GhcPs -> Sig GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Sig GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) Source #

Data (IPBind GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPBind GhcTc -> c (IPBind GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcTc) Source #

toConstr :: IPBind GhcTc -> Constr Source #

dataTypeOf :: IPBind GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> IPBind GhcTc -> IPBind GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) Source #

Data (IPBind GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPBind GhcRn -> c (IPBind GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcRn) Source #

toConstr :: IPBind GhcRn -> Constr Source #

dataTypeOf :: IPBind GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> IPBind GhcRn -> IPBind GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) Source #

Data (IPBind GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPBind GhcPs -> c (IPBind GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcPs) Source #

toConstr :: IPBind GhcPs -> Constr Source #

dataTypeOf :: IPBind GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> IPBind GhcPs -> IPBind GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) Source #

Data (HsIPBinds GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPBinds GhcTc -> c (HsIPBinds GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcTc) Source #

toConstr :: HsIPBinds GhcTc -> Constr Source #

dataTypeOf :: HsIPBinds GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcTc -> HsIPBinds GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) Source #

Data (HsIPBinds GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPBinds GhcRn -> c (HsIPBinds GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcRn) Source #

toConstr :: HsIPBinds GhcRn -> Constr Source #

dataTypeOf :: HsIPBinds GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcRn -> HsIPBinds GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) Source #

Data (HsIPBinds GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPBinds GhcPs -> c (HsIPBinds GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcPs) Source #

toConstr :: HsIPBinds GhcPs -> Constr Source #

dataTypeOf :: HsIPBinds GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcPs -> HsIPBinds GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) Source #

Data (ABExport GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABExport GhcTc -> c (ABExport GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ABExport GhcTc) Source #

toConstr :: ABExport GhcTc -> Constr Source #

dataTypeOf :: ABExport GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ABExport GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ABExport GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ABExport GhcTc -> ABExport GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ABExport GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ABExport GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ABExport GhcTc -> m (ABExport GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcTc -> m (ABExport GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcTc -> m (ABExport GhcTc) Source #

Data (ABExport GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABExport GhcRn -> c (ABExport GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ABExport GhcRn) Source #

toConstr :: ABExport GhcRn -> Constr Source #

dataTypeOf :: ABExport GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ABExport GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ABExport GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ABExport GhcRn -> ABExport GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ABExport GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ABExport GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ABExport GhcRn -> m (ABExport GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcRn -> m (ABExport GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcRn -> m (ABExport GhcRn) Source #

Data (ABExport GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABExport GhcPs -> c (ABExport GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ABExport GhcPs) Source #

toConstr :: ABExport GhcPs -> Constr Source #

dataTypeOf :: ABExport GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ABExport GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ABExport GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ABExport GhcPs -> ABExport GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ABExport GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ABExport GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ABExport GhcPs -> m (ABExport GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcPs -> m (ABExport GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcPs -> m (ABExport GhcPs) Source #

Data (NHsValBindsLR GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcTc -> c (NHsValBindsLR GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcTc) Source #

toConstr :: NHsValBindsLR GhcTc -> Constr Source #

dataTypeOf :: NHsValBindsLR GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcTc -> NHsValBindsLR GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) Source #

Data (NHsValBindsLR GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcRn -> c (NHsValBindsLR GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcRn) Source #

toConstr :: NHsValBindsLR GhcRn -> Constr Source #

dataTypeOf :: NHsValBindsLR GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcRn -> NHsValBindsLR GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) Source #

Data (NHsValBindsLR GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcPs -> c (NHsValBindsLR GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcPs) Source #

toConstr :: NHsValBindsLR GhcPs -> Constr Source #

dataTypeOf :: NHsValBindsLR GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcPs -> NHsValBindsLR GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) Source #

Data (RoleAnnotDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcTc -> c (RoleAnnotDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcTc) Source #

toConstr :: RoleAnnotDecl GhcTc -> Constr Source #

dataTypeOf :: RoleAnnotDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcTc -> RoleAnnotDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source #

Data (RoleAnnotDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcRn -> c (RoleAnnotDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcRn) Source #

toConstr :: RoleAnnotDecl GhcRn -> Constr Source #

dataTypeOf :: RoleAnnotDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcRn -> RoleAnnotDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source #

Data (RoleAnnotDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcPs -> c (RoleAnnotDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcPs) Source #

toConstr :: RoleAnnotDecl GhcPs -> Constr Source #

dataTypeOf :: RoleAnnotDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcPs -> RoleAnnotDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source #

Data (AnnDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: AnnDecl GhcTc -> Constr Source #

dataTypeOf :: AnnDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (AnnDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: AnnDecl GhcRn -> Constr Source #

dataTypeOf :: AnnDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (AnnDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

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

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

toConstr :: AnnDecl GhcPs -> Constr Source #

dataTypeOf :: AnnDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (WarnDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcTc -> c (WarnDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcTc) Source #

toConstr :: WarnDecl GhcTc -> Constr Source #

dataTypeOf :: WarnDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcTc -> WarnDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source #

Data (WarnDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcRn -> c (WarnDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcRn) Source #

toConstr :: WarnDecl GhcRn -> Constr Source #

dataTypeOf :: WarnDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcRn -> WarnDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source #

Data (WarnDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcPs -> c (WarnDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcPs) Source #

toConstr :: WarnDecl GhcPs -> Constr Source #

dataTypeOf :: WarnDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcPs -> WarnDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source #

Data (WarnDecls GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcTc -> c (WarnDecls GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcTc) Source #

toConstr :: WarnDecls GhcTc -> Constr Source #

dataTypeOf :: WarnDecls GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcTc -> WarnDecls GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source #

Data (WarnDecls GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcRn -> c (WarnDecls GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcRn) Source #

toConstr :: WarnDecls GhcRn -> Constr Source #

dataTypeOf :: WarnDecls GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcRn -> WarnDecls GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source #

Data (WarnDecls GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcPs -> c (WarnDecls GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcPs) Source #

toConstr :: WarnDecls GhcPs -> Constr Source #

dataTypeOf :: WarnDecls GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcPs -> WarnDecls GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source #

Data (RuleBndr GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcTc -> c (RuleBndr GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcTc) Source #

toConstr :: RuleBndr GhcTc -> Constr Source #

dataTypeOf :: RuleBndr GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcTc -> RuleBndr GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source #

Data (RuleBndr GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcRn -> c (RuleBndr GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcRn) Source #

toConstr :: RuleBndr GhcRn -> Constr Source #

dataTypeOf :: RuleBndr GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcRn -> RuleBndr GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source #

Data (RuleBndr GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcPs -> c (RuleBndr GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcPs) Source #

toConstr :: RuleBndr GhcPs -> Constr Source #

dataTypeOf :: RuleBndr GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcPs -> RuleBndr GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source #

Data (RuleDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcTc -> c (RuleDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcTc) Source #

toConstr :: RuleDecl GhcTc -> Constr Source #

dataTypeOf :: RuleDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcTc -> RuleDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source #

Data (RuleDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcRn -> c (RuleDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcRn) Source #

toConstr :: RuleDecl GhcRn -> Constr Source #

dataTypeOf :: RuleDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcRn -> RuleDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source #

Data (RuleDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcPs -> c (RuleDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcPs) Source #

toConstr :: RuleDecl GhcPs -> Constr Source #

dataTypeOf :: RuleDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcPs -> RuleDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source #

Data (RuleDecls GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcTc -> c (RuleDecls GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcTc) Source #

toConstr :: RuleDecls GhcTc -> Constr Source #

dataTypeOf :: RuleDecls GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcTc -> RuleDecls GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source #

Data (RuleDecls GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcRn -> c (RuleDecls GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcRn) Source #

toConstr :: RuleDecls GhcRn -> Constr Source #

dataTypeOf :: RuleDecls GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcRn -> RuleDecls GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source #

Data (RuleDecls GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcPs -> c (RuleDecls GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcPs) Source #

toConstr :: RuleDecls GhcPs -> Constr Source #

dataTypeOf :: RuleDecls GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcPs -> RuleDecls GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source #

Data (ForeignDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignDecl GhcTc -> c (ForeignDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcTc) Source #

toConstr :: ForeignDecl GhcTc -> Constr Source #

dataTypeOf :: ForeignDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcTc -> ForeignDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) Source #

Data (ForeignDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignDecl GhcRn -> c (ForeignDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcRn) Source #

toConstr :: ForeignDecl GhcRn -> Constr Source #

dataTypeOf :: ForeignDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcRn -> ForeignDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) Source #

Data (ForeignDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignDecl GhcPs -> c (ForeignDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcPs) Source #

toConstr :: ForeignDecl GhcPs -> Constr Source #

dataTypeOf :: ForeignDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcPs -> ForeignDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) Source #

Data (DefaultDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultDecl GhcTc -> c (DefaultDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcTc) Source #

toConstr :: DefaultDecl GhcTc -> Constr Source #

dataTypeOf :: DefaultDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcTc -> DefaultDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) Source #

Data (DefaultDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultDecl GhcRn -> c (DefaultDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcRn) Source #

toConstr :: DefaultDecl GhcRn -> Constr Source #

dataTypeOf :: DefaultDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcRn -> DefaultDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) Source #

Data (DefaultDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultDecl GhcPs -> c (DefaultDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcPs) Source #

toConstr :: DefaultDecl GhcPs -> Constr Source #

dataTypeOf :: DefaultDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcPs -> DefaultDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) Source #

Data (DerivStrategy GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivStrategy GhcTc -> c (DerivStrategy GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcTc) Source #

toConstr :: DerivStrategy GhcTc -> Constr Source #

dataTypeOf :: DerivStrategy GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcTc -> DerivStrategy GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) Source #

Data (DerivStrategy GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivStrategy GhcRn -> c (DerivStrategy GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcRn) Source #

toConstr :: DerivStrategy GhcRn -> Constr Source #

dataTypeOf :: DerivStrategy GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcRn -> DerivStrategy GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) Source #

Data (DerivStrategy GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivStrategy GhcPs -> c (DerivStrategy GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcPs) Source #

toConstr :: DerivStrategy GhcPs -> Constr Source #

dataTypeOf :: DerivStrategy GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcPs -> DerivStrategy GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) Source #

Data (DerivDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivDecl GhcTc -> c (DerivDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcTc) Source #

toConstr :: DerivDecl GhcTc -> Constr Source #

dataTypeOf :: DerivDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcTc -> DerivDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) Source #

Data (DerivDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivDecl GhcRn -> c (DerivDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcRn) Source #

toConstr :: DerivDecl GhcRn -> Constr Source #

dataTypeOf :: DerivDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcRn -> DerivDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) Source #

Data (DerivDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivDecl GhcPs -> c (DerivDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcPs) Source #

toConstr :: DerivDecl GhcPs -> Constr Source #

dataTypeOf :: DerivDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcPs -> DerivDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) Source #

Data (InstDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcTc -> c (InstDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcTc) Source #

toConstr :: InstDecl GhcTc -> Constr Source #

dataTypeOf :: InstDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcTc -> InstDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source #

Data (InstDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcRn -> c (InstDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcRn) Source #

toConstr :: InstDecl GhcRn -> Constr Source #

dataTypeOf :: InstDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcRn -> InstDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source #

Data (InstDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcPs -> c (InstDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcPs) Source #

toConstr :: InstDecl GhcPs -> Constr Source #

dataTypeOf :: InstDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcPs -> InstDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source #

Data (ClsInstDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInstDecl GhcTc -> c (ClsInstDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcTc) Source #

toConstr :: ClsInstDecl GhcTc -> Constr Source #

dataTypeOf :: ClsInstDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcTc -> ClsInstDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) Source #

Data (ClsInstDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInstDecl GhcRn -> c (ClsInstDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcRn) Source #

toConstr :: ClsInstDecl GhcRn -> Constr Source #

dataTypeOf :: ClsInstDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcRn -> ClsInstDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) Source #

Data (ClsInstDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInstDecl GhcPs -> c (ClsInstDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcPs) Source #

toConstr :: ClsInstDecl GhcPs -> Constr Source #

dataTypeOf :: ClsInstDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcPs -> ClsInstDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) Source #

Data (DataFamInstDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataFamInstDecl GhcTc -> c (DataFamInstDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcTc) Source #

toConstr :: DataFamInstDecl GhcTc -> Constr Source #

dataTypeOf :: DataFamInstDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcTc -> DataFamInstDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) Source #

Data (DataFamInstDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataFamInstDecl GhcRn -> c (DataFamInstDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcRn) Source #

toConstr :: DataFamInstDecl GhcRn -> Constr Source #

dataTypeOf :: DataFamInstDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcRn -> DataFamInstDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) Source #

Data (DataFamInstDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataFamInstDecl GhcPs -> c (DataFamInstDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcPs) Source #

toConstr :: DataFamInstDecl GhcPs -> Constr Source #

dataTypeOf :: DataFamInstDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcPs -> DataFamInstDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) Source #

Data (TyFamInstDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcTc -> c (TyFamInstDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcTc) Source #

toConstr :: TyFamInstDecl GhcTc -> Constr Source #

dataTypeOf :: TyFamInstDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcTc -> TyFamInstDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source #

Data (TyFamInstDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcRn -> c (TyFamInstDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcRn) Source #

toConstr :: TyFamInstDecl GhcRn -> Constr Source #

dataTypeOf :: TyFamInstDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcRn -> TyFamInstDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source #

Data (TyFamInstDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcPs -> c (TyFamInstDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcPs) Source #

toConstr :: TyFamInstDecl GhcPs -> Constr Source #

dataTypeOf :: TyFamInstDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcPs -> TyFamInstDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source #

Data (ConDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDecl GhcTc -> c (ConDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcTc) Source #

toConstr :: ConDecl GhcTc -> Constr Source #

dataTypeOf :: ConDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcTc -> ConDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) Source #

Data (ConDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDecl GhcRn -> c (ConDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcRn) Source #

toConstr :: ConDecl GhcRn -> Constr Source #

dataTypeOf :: ConDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcRn -> ConDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) Source #

Data (ConDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDecl GhcPs -> c (ConDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcPs) Source #

toConstr :: ConDecl GhcPs -> Constr Source #

dataTypeOf :: ConDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcPs -> ConDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) Source #

Data (HsDerivingClause GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDerivingClause GhcTc -> c (HsDerivingClause GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcTc) Source #

toConstr :: HsDerivingClause GhcTc -> Constr Source #

dataTypeOf :: HsDerivingClause GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcTc -> HsDerivingClause GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) Source #

Data (HsDerivingClause GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDerivingClause GhcRn -> c (HsDerivingClause GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcRn) Source #

toConstr :: HsDerivingClause GhcRn -> Constr Source #

dataTypeOf :: HsDerivingClause GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcRn -> HsDerivingClause GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) Source #

Data (HsDerivingClause GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDerivingClause GhcPs -> c (HsDerivingClause GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcPs) Source #

toConstr :: HsDerivingClause GhcPs -> Constr Source #

dataTypeOf :: HsDerivingClause GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcPs -> HsDerivingClause GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) Source #

Data (HsDataDefn GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDataDefn GhcTc -> c (HsDataDefn GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcTc) Source #

toConstr :: HsDataDefn GhcTc -> Constr Source #

dataTypeOf :: HsDataDefn GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcTc -> HsDataDefn GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) Source #

Data (HsDataDefn GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDataDefn GhcRn -> c (HsDataDefn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcRn) Source #

toConstr :: HsDataDefn GhcRn -> Constr Source #

dataTypeOf :: HsDataDefn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcRn -> HsDataDefn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) Source #

Data (HsDataDefn GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDataDefn GhcPs -> c (HsDataDefn GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcPs) Source #

toConstr :: HsDataDefn GhcPs -> Constr Source #

dataTypeOf :: HsDataDefn GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcPs -> HsDataDefn GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) Source #

Data (FamilyInfo GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyInfo GhcTc -> c (FamilyInfo GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcTc) Source #

toConstr :: FamilyInfo GhcTc -> Constr Source #

dataTypeOf :: FamilyInfo GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcTc -> FamilyInfo GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) Source #

Data (FamilyInfo GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyInfo GhcRn -> c (FamilyInfo GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcRn) Source #

toConstr :: FamilyInfo GhcRn -> Constr Source #

dataTypeOf :: FamilyInfo GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcRn -> FamilyInfo GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) Source #

Data (FamilyInfo GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyInfo GhcPs -> c (FamilyInfo GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcPs) Source #

toConstr :: FamilyInfo GhcPs -> Constr Source #

dataTypeOf :: FamilyInfo GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcPs -> FamilyInfo GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) Source #

Data (InjectivityAnn GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcTc -> c (InjectivityAnn GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcTc) Source #

toConstr :: InjectivityAnn GhcTc -> Constr Source #

dataTypeOf :: InjectivityAnn GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcTc -> InjectivityAnn GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source #

Data (InjectivityAnn GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcRn -> c (InjectivityAnn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcRn) Source #

toConstr :: InjectivityAnn GhcRn -> Constr Source #

dataTypeOf :: InjectivityAnn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcRn -> InjectivityAnn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source #

Data (InjectivityAnn GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcPs -> c (InjectivityAnn GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcPs) Source #

toConstr :: InjectivityAnn GhcPs -> Constr Source #

dataTypeOf :: InjectivityAnn GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcPs -> InjectivityAnn GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source #

Data (FamilyDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyDecl GhcTc -> c (FamilyDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcTc) Source #

toConstr :: FamilyDecl GhcTc -> Constr Source #

dataTypeOf :: FamilyDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcTc -> FamilyDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) Source #

Data (FamilyDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyDecl GhcRn -> c (FamilyDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcRn) Source #

toConstr :: FamilyDecl GhcRn -> Constr Source #

dataTypeOf :: FamilyDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcRn -> FamilyDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) Source #

Data (FamilyDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyDecl GhcPs -> c (FamilyDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcPs) Source #

toConstr :: FamilyDecl GhcPs -> Constr Source #

dataTypeOf :: FamilyDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcPs -> FamilyDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) Source #

Data (FamilyResultSig GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyResultSig GhcTc -> c (FamilyResultSig GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcTc) Source #

toConstr :: FamilyResultSig GhcTc -> Constr Source #

dataTypeOf :: FamilyResultSig GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcTc -> FamilyResultSig GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) Source #

Data (FamilyResultSig GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyResultSig GhcRn -> c (FamilyResultSig GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcRn) Source #

toConstr :: FamilyResultSig GhcRn -> Constr Source #

dataTypeOf :: FamilyResultSig GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcRn -> FamilyResultSig GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) Source #

Data (FamilyResultSig GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyResultSig GhcPs -> c (FamilyResultSig GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcPs) Source #

toConstr :: FamilyResultSig GhcPs -> Constr Source #

dataTypeOf :: FamilyResultSig GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcPs -> FamilyResultSig GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) Source #

Data (TyClGroup GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcTc -> c (TyClGroup GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcTc) Source #

toConstr :: TyClGroup GhcTc -> Constr Source #

dataTypeOf :: TyClGroup GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcTc -> TyClGroup GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source #

Data (TyClGroup GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcRn -> c (TyClGroup GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcRn) Source #

toConstr :: TyClGroup GhcRn -> Constr Source #

dataTypeOf :: TyClGroup GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcRn -> TyClGroup GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source #

Data (TyClGroup GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcPs -> c (TyClGroup GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcPs) Source #

toConstr :: TyClGroup GhcPs -> Constr Source #

dataTypeOf :: TyClGroup GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcPs -> TyClGroup GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source #

Data (TyClDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcTc -> c (TyClDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcTc) Source #

toConstr :: TyClDecl GhcTc -> Constr Source #

dataTypeOf :: TyClDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcTc -> TyClDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source #

Data (TyClDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcRn -> c (TyClDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcRn) Source #

toConstr :: TyClDecl GhcRn -> Constr Source #

dataTypeOf :: TyClDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcRn -> TyClDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source #

Data (TyClDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcPs -> c (TyClDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcPs) Source #

toConstr :: TyClDecl GhcPs -> Constr Source #

dataTypeOf :: TyClDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcPs -> TyClDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source #

Data (SpliceDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcTc -> c (SpliceDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcTc) Source #

toConstr :: SpliceDecl GhcTc -> Constr Source #

dataTypeOf :: SpliceDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcTc -> SpliceDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source #

Data (SpliceDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcRn -> c (SpliceDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcRn) Source #

toConstr :: SpliceDecl GhcRn -> Constr Source #

dataTypeOf :: SpliceDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcRn -> SpliceDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source #

Data (SpliceDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcPs -> c (SpliceDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcPs) Source #

toConstr :: SpliceDecl GhcPs -> Constr Source #

dataTypeOf :: SpliceDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcPs -> SpliceDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source #

Data (HsGroup GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGroup GhcTc -> c (HsGroup GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcTc) Source #

toConstr :: HsGroup GhcTc -> Constr Source #

dataTypeOf :: HsGroup GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcTc -> HsGroup GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source #

Data (HsGroup GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGroup GhcRn -> c (HsGroup GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcRn) Source #

toConstr :: HsGroup GhcRn -> Constr Source #

dataTypeOf :: HsGroup GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcRn -> HsGroup GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source #

Data (HsGroup GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGroup GhcPs -> c (HsGroup GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcPs) Source #

toConstr :: HsGroup GhcPs -> Constr Source #

dataTypeOf :: HsGroup GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcPs -> HsGroup GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) Source #

Data (HsDecl GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDecl GhcTc -> c (HsDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcTc) Source #

toConstr :: HsDecl GhcTc -> Constr Source #

dataTypeOf :: HsDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcTc -> HsDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) Source #

Data (HsDecl GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDecl GhcRn -> c (HsDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcRn) Source #

toConstr :: HsDecl GhcRn -> Constr Source #

dataTypeOf :: HsDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcRn -> HsDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) Source #

Data (HsDecl GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDecl GhcPs -> c (HsDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcPs) Source #

toConstr :: HsDecl GhcPs -> Constr Source #

dataTypeOf :: HsDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcPs -> HsDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) Source #

Data (ArithSeqInfo GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcTc -> c (ArithSeqInfo GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcTc) Source #

toConstr :: ArithSeqInfo GhcTc -> Constr Source #

dataTypeOf :: ArithSeqInfo GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcTc -> ArithSeqInfo GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source #

Data (ArithSeqInfo GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcRn -> c (ArithSeqInfo GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcRn) Source #

toConstr :: ArithSeqInfo GhcRn -> Constr Source #

dataTypeOf :: ArithSeqInfo GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcRn -> ArithSeqInfo GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source #

Data (ArithSeqInfo GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcPs -> c (ArithSeqInfo GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcPs) Source #

toConstr :: ArithSeqInfo GhcPs -> Constr Source #

dataTypeOf :: ArithSeqInfo GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcPs -> ArithSeqInfo GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source #

Data (HsBracket GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcTc -> c (HsBracket GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcTc) Source #

toConstr :: HsBracket GhcTc -> Constr Source #

dataTypeOf :: HsBracket GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcTc -> HsBracket GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) Source #

Data (HsBracket GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcRn -> c (HsBracket GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcRn) Source #

toConstr :: HsBracket GhcRn -> Constr Source #

dataTypeOf :: HsBracket GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcRn -> HsBracket GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) Source #

Data (HsBracket GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcPs -> c (HsBracket GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcPs) Source #

toConstr :: HsBracket GhcPs -> Constr Source #

dataTypeOf :: HsBracket GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcPs -> HsBracket GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) Source #

Data (HsSplicedThing GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcTc -> c (HsSplicedThing GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcTc) Source #

toConstr :: HsSplicedThing GhcTc -> Constr Source #

dataTypeOf :: HsSplicedThing GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcTc -> HsSplicedThing GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) Source #

Data (HsSplicedThing GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcRn -> c (HsSplicedThing GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcRn) Source #

toConstr :: HsSplicedThing GhcRn -> Constr Source #

dataTypeOf :: HsSplicedThing GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcRn -> HsSplicedThing GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) Source #

Data (HsSplicedThing GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcPs -> c (HsSplicedThing GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcPs) Source #

toConstr :: HsSplicedThing GhcPs -> Constr Source #

dataTypeOf :: HsSplicedThing GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcPs -> HsSplicedThing GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) Source #

Data (ApplicativeArg GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcTc -> c (ApplicativeArg GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcTc) Source #

toConstr :: ApplicativeArg GhcTc -> Constr Source #

dataTypeOf :: ApplicativeArg GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcTc -> ApplicativeArg GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source #

Data (ApplicativeArg GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcRn -> c (ApplicativeArg GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcRn) Source #

toConstr :: ApplicativeArg GhcRn -> Constr Source #

dataTypeOf :: ApplicativeArg GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcRn -> ApplicativeArg GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source #

Data (ApplicativeArg GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcPs -> c (ApplicativeArg GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcPs) Source #

toConstr :: ApplicativeArg GhcPs -> Constr Source #

dataTypeOf :: ApplicativeArg GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcPs -> ApplicativeArg GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source #

Data (HsCmdTop GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcTc -> c (HsCmdTop GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcTc) Source #

toConstr :: HsCmdTop GhcTc -> Constr Source #

dataTypeOf :: HsCmdTop GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcTc -> HsCmdTop GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source #

Data (HsCmdTop GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcRn -> c (HsCmdTop GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcRn) Source #

toConstr :: HsCmdTop GhcRn -> Constr Source #

dataTypeOf :: HsCmdTop GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcRn -> HsCmdTop GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source #

Data (HsCmdTop GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcPs -> c (HsCmdTop GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcPs) Source #

toConstr :: HsCmdTop GhcPs -> Constr Source #

dataTypeOf :: HsCmdTop GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcPs -> HsCmdTop GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source #

Data (HsTupArg GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcTc -> c (HsTupArg GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcTc) Source #

toConstr :: HsTupArg GhcTc -> Constr Source #

dataTypeOf :: HsTupArg GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcTc -> HsTupArg GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source #

Data (HsTupArg GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcRn -> c (HsTupArg GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcRn) Source #

toConstr :: HsTupArg GhcRn -> Constr Source #

dataTypeOf :: HsTupArg GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcRn -> HsTupArg GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source #

Data (HsTupArg GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcPs -> c (HsTupArg GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcPs) Source #

toConstr :: HsTupArg GhcPs -> Constr Source #

dataTypeOf :: HsTupArg GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcPs -> HsTupArg GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source #

Data (HsModule GhcTc) # 
Instance details

Defined in HsSyn

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcTc -> c (HsModule GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcTc) Source #

toConstr :: HsModule GhcTc -> Constr Source #

dataTypeOf :: HsModule GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsModule GhcTc -> HsModule GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) Source #

Data (HsModule GhcRn) # 
Instance details

Defined in HsSyn

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcRn -> c (HsModule GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcRn) Source #

toConstr :: HsModule GhcRn -> Constr Source #

dataTypeOf :: HsModule GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsModule GhcRn -> HsModule GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) Source #

Data (HsModule GhcPs) # 
Instance details

Defined in HsSyn

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcPs -> c (HsModule GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcPs) Source #

toConstr :: HsModule GhcPs -> Constr Source #

dataTypeOf :: HsModule GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsModule GhcPs -> HsModule GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source #

OutputableBndrId (GhcPass a) => Outputable (InstInfo (GhcPass a)) # 
Instance details

Defined in TcEnv

HasSrcSpan (LPat (GhcPass p)) # 
Instance details

Defined in HsPat

Data body => Data (GRHSs GhcTc body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc body -> c (GRHSs GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc body) Source #

toConstr :: GRHSs GhcTc body -> Constr Source #

dataTypeOf :: GRHSs GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc body -> GRHSs GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) Source #

Data body => Data (GRHSs GhcRn body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn body -> c (GRHSs GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn body) Source #

toConstr :: GRHSs GhcRn body -> Constr Source #

dataTypeOf :: GRHSs GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn body -> GRHSs GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) Source #

Data body => Data (GRHSs GhcPs body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs body -> c (GRHSs GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs body) Source #

toConstr :: GRHSs GhcPs body -> Constr Source #

dataTypeOf :: GRHSs GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs body -> GRHSs GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) Source #

Data body => Data (MatchGroup GhcTc body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc body -> c (MatchGroup GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc body) Source #

toConstr :: MatchGroup GhcTc body -> Constr Source #

dataTypeOf :: MatchGroup GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc body -> MatchGroup GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) Source #

Data body => Data (MatchGroup GhcRn body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn body -> c (MatchGroup GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn body) Source #

toConstr :: MatchGroup GhcRn body -> Constr Source #

dataTypeOf :: MatchGroup GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn body -> MatchGroup GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) Source #

Data body => Data (MatchGroup GhcPs body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs body -> c (MatchGroup GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs body) Source #

toConstr :: MatchGroup GhcPs body -> Constr Source #

dataTypeOf :: MatchGroup GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs body -> MatchGroup GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) Source #

Data (HsArg (LHsType GhcTc) (LHsKind GhcTc)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source #

toConstr :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcTc) (LHsKind GhcTc))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcTc) (LHsKind GhcTc))) Source #

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) Source #

Data (HsArg (LHsType GhcRn) (LHsKind GhcRn)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source #

toConstr :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcRn) (LHsKind GhcRn))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcRn) (LHsKind GhcRn))) Source #

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) Source #

Data (HsArg (LHsType GhcPs) (LHsKind GhcPs)) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source #

toConstr :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> Constr Source #

dataTypeOf :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcPs) (LHsKind GhcPs))) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcPs) (LHsKind GhcPs))) Source #

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) Source #

Data thing => Data (HsWildCardBndrs GhcTc thing) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcTc thing -> c (HsWildCardBndrs GhcTc thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcTc thing) Source #

toConstr :: HsWildCardBndrs GhcTc thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcTc thing -> HsWildCardBndrs GhcTc thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source #

Data thing => Data (HsWildCardBndrs GhcRn thing) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcRn thing -> c (HsWildCardBndrs GhcRn thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcRn thing) Source #

toConstr :: HsWildCardBndrs GhcRn thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcRn thing -> HsWildCardBndrs GhcRn thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source #

Data thing => Data (HsWildCardBndrs GhcPs thing) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcPs thing -> c (HsWildCardBndrs GhcPs thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcPs thing) Source #

toConstr :: HsWildCardBndrs GhcPs thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcPs thing -> HsWildCardBndrs GhcPs thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source #

Data thing => Data (HsImplicitBndrs GhcTc thing) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplicitBndrs GhcTc thing -> c (HsImplicitBndrs GhcTc thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcTc thing) Source #

toConstr :: HsImplicitBndrs GhcTc thing -> Constr Source #

dataTypeOf :: HsImplicitBndrs GhcTc thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcTc thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcTc thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcTc thing -> HsImplicitBndrs GhcTc thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcTc thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcTc thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcTc thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcTc thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) Source #

Data thing => Data (HsImplicitBndrs GhcRn thing) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplicitBndrs GhcRn thing -> c (HsImplicitBndrs GhcRn thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcRn thing) Source #

toConstr :: HsImplicitBndrs GhcRn thing -> Constr Source #

dataTypeOf :: HsImplicitBndrs GhcRn thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcRn thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcRn thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcRn thing -> HsImplicitBndrs GhcRn thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcRn thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcRn thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcRn thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcRn thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) Source #

Data thing => Data (HsImplicitBndrs GhcPs thing) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplicitBndrs GhcPs thing -> c (HsImplicitBndrs GhcPs thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcPs thing) Source #

toConstr :: HsImplicitBndrs GhcPs thing -> Constr Source #

dataTypeOf :: HsImplicitBndrs GhcPs thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcPs thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcPs thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcPs thing -> HsImplicitBndrs GhcPs thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcPs thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcPs thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcPs thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcPs thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) Source #

Data (PatSynBind GhcTc GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcTc GhcTc -> c (PatSynBind GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcTc GhcTc) Source #

toConstr :: PatSynBind GhcTc GhcTc -> Constr Source #

dataTypeOf :: PatSynBind GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcTc GhcTc -> PatSynBind GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source #

Data (PatSynBind GhcRn GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcRn GhcRn -> c (PatSynBind GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcRn GhcRn) Source #

toConstr :: PatSynBind GhcRn GhcRn -> Constr Source #

dataTypeOf :: PatSynBind GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcRn GhcRn -> PatSynBind GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source #

Data (PatSynBind GhcPs GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcPs GhcRn -> c (PatSynBind GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcRn) Source #

toConstr :: PatSynBind GhcPs GhcRn -> Constr Source #

dataTypeOf :: PatSynBind GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcRn -> PatSynBind GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source #

Data (PatSynBind GhcPs GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcPs GhcPs -> c (PatSynBind GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcPs) Source #

toConstr :: PatSynBind GhcPs GhcPs -> Constr Source #

dataTypeOf :: PatSynBind GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcPs -> PatSynBind GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source #

Data (HsBindLR GhcTc GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcTc GhcTc -> c (HsBindLR GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcTc GhcTc) Source #

toConstr :: HsBindLR GhcTc GhcTc -> Constr Source #

dataTypeOf :: HsBindLR GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcTc GhcTc -> HsBindLR GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source #

Data (HsBindLR GhcRn GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcRn GhcRn -> c (HsBindLR GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcRn GhcRn) Source #

toConstr :: HsBindLR GhcRn GhcRn -> Constr Source #

dataTypeOf :: HsBindLR GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcRn GhcRn -> HsBindLR GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source #

Data (HsBindLR GhcPs GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcPs GhcRn -> c (HsBindLR GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcRn) Source #

toConstr :: HsBindLR GhcPs GhcRn -> Constr Source #

dataTypeOf :: HsBindLR GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcRn -> HsBindLR GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source #

Data (HsBindLR GhcPs GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcPs GhcPs -> c (HsBindLR GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcPs) Source #

toConstr :: HsBindLR GhcPs GhcPs -> Constr Source #

dataTypeOf :: HsBindLR GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcPs -> HsBindLR GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source #

Data (HsValBindsLR GhcTc GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcTc GhcTc -> c (HsValBindsLR GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcTc GhcTc) Source #

toConstr :: HsValBindsLR GhcTc GhcTc -> Constr Source #

dataTypeOf :: HsValBindsLR GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcTc GhcTc -> HsValBindsLR GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source #

Data (HsValBindsLR GhcRn GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcRn GhcRn -> c (HsValBindsLR GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcRn GhcRn) Source #

toConstr :: HsValBindsLR GhcRn GhcRn -> Constr Source #

dataTypeOf :: HsValBindsLR GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcRn GhcRn -> HsValBindsLR GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source #

Data (HsValBindsLR GhcPs GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcPs GhcRn -> c (HsValBindsLR GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcRn) Source #

toConstr :: HsValBindsLR GhcPs GhcRn -> Constr Source #

dataTypeOf :: HsValBindsLR GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcRn -> HsValBindsLR GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source #

Data (HsValBindsLR GhcPs GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcPs GhcPs -> c (HsValBindsLR GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcPs) Source #

toConstr :: HsValBindsLR GhcPs GhcPs -> Constr Source #

dataTypeOf :: HsValBindsLR GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcPs -> HsValBindsLR GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source #

Data (HsLocalBindsLR GhcTc GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcTc GhcTc -> c (HsLocalBindsLR GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcTc GhcTc) Source #

toConstr :: HsLocalBindsLR GhcTc GhcTc -> Constr Source #

dataTypeOf :: HsLocalBindsLR GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcTc GhcTc -> HsLocalBindsLR GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source #

Data (HsLocalBindsLR GhcRn GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcRn GhcRn -> c (HsLocalBindsLR GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcRn GhcRn) Source #

toConstr :: HsLocalBindsLR GhcRn GhcRn -> Constr Source #

dataTypeOf :: HsLocalBindsLR GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcRn GhcRn -> HsLocalBindsLR GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source #

Data (HsLocalBindsLR GhcPs GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcPs GhcRn -> c (HsLocalBindsLR GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcRn) Source #

toConstr :: HsLocalBindsLR GhcPs GhcRn -> Constr Source #

dataTypeOf :: HsLocalBindsLR GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcRn -> HsLocalBindsLR GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source #

Data (HsLocalBindsLR GhcPs GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcPs GhcPs -> c (HsLocalBindsLR GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcPs) Source #

toConstr :: HsLocalBindsLR GhcPs GhcPs -> Constr Source #

dataTypeOf :: HsLocalBindsLR GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcPs -> HsLocalBindsLR GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source #

Data body => Data (HsRecFields GhcTc body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcTc body -> c (HsRecFields GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcTc body) Source #

toConstr :: HsRecFields GhcTc body -> Constr Source #

dataTypeOf :: HsRecFields GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcTc body -> HsRecFields GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source #

Data body => Data (HsRecFields GhcRn body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcRn body -> c (HsRecFields GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcRn body) Source #

toConstr :: HsRecFields GhcRn body -> Constr Source #

dataTypeOf :: HsRecFields GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcRn body -> HsRecFields GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source #

Data body => Data (HsRecFields GhcPs body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcPs body -> c (HsRecFields GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcPs body) Source #

toConstr :: HsRecFields GhcPs body -> Constr Source #

dataTypeOf :: HsRecFields GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcPs body -> HsRecFields GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source #

Data (ParStmtBlock GhcTc GhcTc) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcTc GhcTc -> c (ParStmtBlock GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcTc GhcTc) Source #

toConstr :: ParStmtBlock GhcTc GhcTc -> Constr Source #

dataTypeOf :: ParStmtBlock GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcTc GhcTc -> ParStmtBlock GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source #

Data (ParStmtBlock GhcRn GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcRn GhcRn -> c (ParStmtBlock GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcRn GhcRn) Source #

toConstr :: ParStmtBlock GhcRn GhcRn -> Constr Source #

dataTypeOf :: ParStmtBlock GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcRn GhcRn -> ParStmtBlock GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source #

Data (ParStmtBlock GhcPs GhcRn) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcPs GhcRn -> c (ParStmtBlock GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcRn) Source #

toConstr :: ParStmtBlock GhcPs GhcRn -> Constr Source #

dataTypeOf :: ParStmtBlock GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcRn -> ParStmtBlock GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source #

Data (ParStmtBlock GhcPs GhcPs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcPs GhcPs -> c (ParStmtBlock GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcPs) Source #

toConstr :: ParStmtBlock GhcPs GhcPs -> Constr Source #

dataTypeOf :: ParStmtBlock GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcPs -> ParStmtBlock GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source #

Data body => Data (GRHS GhcTc body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc body -> c (GRHS GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc body) Source #

toConstr :: GRHS GhcTc body -> Constr Source #

dataTypeOf :: GRHS GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc body -> GRHS GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) Source #

Data body => Data (GRHS GhcRn body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn body -> c (GRHS GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn body) Source #

toConstr :: GRHS GhcRn body -> Constr Source #

dataTypeOf :: GRHS GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn body -> GRHS GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) Source #

Data body => Data (GRHS GhcPs body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs body -> c (GRHS GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs body) Source #

toConstr :: GRHS GhcPs body -> Constr Source #

dataTypeOf :: GRHS GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs body -> GRHS GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) Source #

Data body => Data (Match GhcTc body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc body -> c (Match GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc body) Source #

toConstr :: Match GhcTc body -> Constr Source #

dataTypeOf :: Match GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc body -> Match GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) Source #

Data body => Data (Match GhcRn body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn body -> c (Match GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn body) Source #

toConstr :: Match GhcRn body -> Constr Source #

dataTypeOf :: Match GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn body -> Match GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) Source #

Data body => Data (Match GhcPs body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs body -> c (Match GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs body) Source #

toConstr :: Match GhcPs body -> Constr Source #

dataTypeOf :: Match GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs body -> Match GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) Source #

(Data pats, Data rhs) => Data (FamEqn GhcTc pats rhs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamEqn GhcTc pats rhs -> c (FamEqn GhcTc pats rhs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcTc pats rhs) Source #

toConstr :: FamEqn GhcTc pats rhs -> Constr Source #

dataTypeOf :: FamEqn GhcTc pats rhs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcTc pats rhs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcTc pats rhs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcTc pats rhs -> FamEqn GhcTc pats rhs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcTc pats rhs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcTc pats rhs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcTc pats rhs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcTc pats rhs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcTc pats rhs -> m (FamEqn GhcTc pats rhs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcTc pats rhs -> m (FamEqn GhcTc pats rhs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcTc pats rhs -> m (FamEqn GhcTc pats rhs) Source #

(Data pats, Data rhs) => Data (FamEqn GhcRn pats rhs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamEqn GhcRn pats rhs -> c (FamEqn GhcRn pats rhs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcRn pats rhs) Source #

toConstr :: FamEqn GhcRn pats rhs -> Constr Source #

dataTypeOf :: FamEqn GhcRn pats rhs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcRn pats rhs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcRn pats rhs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcRn pats rhs -> FamEqn GhcRn pats rhs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcRn pats rhs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcRn pats rhs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcRn pats rhs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcRn pats rhs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcRn pats rhs -> m (FamEqn GhcRn pats rhs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcRn pats rhs -> m (FamEqn GhcRn pats rhs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcRn pats rhs -> m (FamEqn GhcRn pats rhs) Source #

(Data pats, Data rhs) => Data (FamEqn GhcPs pats rhs) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamEqn GhcPs pats rhs -> c (FamEqn GhcPs pats rhs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcPs pats rhs) Source #

toConstr :: FamEqn GhcPs pats rhs -> Constr Source #

dataTypeOf :: FamEqn GhcPs pats rhs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcPs pats rhs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcPs pats rhs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcPs pats rhs -> FamEqn GhcPs pats rhs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcPs pats rhs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcPs pats rhs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcPs pats rhs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcPs pats rhs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcPs pats rhs -> m (FamEqn GhcPs pats rhs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcPs pats rhs -> m (FamEqn GhcPs pats rhs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcPs pats rhs -> m (FamEqn GhcPs pats rhs) Source #

Data body => Data (StmtLR GhcTc GhcTc body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc body -> c (StmtLR GhcTc GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc body) Source #

toConstr :: StmtLR GhcTc GhcTc body -> Constr Source #

dataTypeOf :: StmtLR GhcTc GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc body -> StmtLR GhcTc GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) Source #

Data body => Data (StmtLR GhcRn GhcRn body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn body -> c (StmtLR GhcRn GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn body) Source #

toConstr :: StmtLR GhcRn GhcRn body -> Constr Source #

dataTypeOf :: StmtLR GhcRn GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn body -> StmtLR GhcRn GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) Source #

Data body => Data (StmtLR GhcPs GhcRn body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn body -> c (StmtLR GhcPs GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn body) Source #

toConstr :: StmtLR GhcPs GhcRn body -> Constr Source #

dataTypeOf :: StmtLR GhcPs GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn body -> StmtLR GhcPs GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) Source #

Data body => Data (StmtLR GhcPs GhcPs body) # 
Instance details

Defined in HsInstances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs body -> c (StmtLR GhcPs GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs body) Source #

toConstr :: StmtLR GhcPs GhcPs body -> Constr Source #

dataTypeOf :: StmtLR GhcPs GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs body -> StmtLR GhcPs GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) Source #

type XCFieldOcc GhcTc # 
Instance details

Defined in HsTypes

type XCFieldOcc GhcRn # 
Instance details

Defined in HsTypes

type XCFieldOcc GhcPs # 
Instance details

Defined in HsTypes

type XExplicitTupleTy GhcTc # 
Instance details

Defined in HsTypes

type XExplicitTupleTy GhcRn # 
Instance details

Defined in HsTypes

type XExplicitTupleTy GhcPs # 
Instance details

Defined in HsTypes

type XExplicitListTy GhcTc # 
Instance details

Defined in HsTypes

type XExplicitListTy GhcRn # 
Instance details

Defined in HsTypes

type XExplicitListTy GhcPs # 
Instance details

Defined in HsTypes

type XSpliceTy GhcTc # 
Instance details

Defined in HsTypes

type XSpliceTy GhcRn # 
Instance details

Defined in HsTypes

type XSpliceTy GhcPs # 
Instance details

Defined in HsTypes

type XHsQTvs GhcTc # 
Instance details

Defined in HsTypes

type XHsQTvs GhcRn # 
Instance details

Defined in HsTypes

type XHsQTvs GhcPs # 
Instance details

Defined in HsTypes

type XSigPat GhcTc # 
Instance details

Defined in HsPat

type XSigPat GhcRn # 
Instance details

Defined in HsPat

type XSigPat GhcPs # 
Instance details

Defined in HsPat

type XNPlusKPat GhcTc # 
Instance details

Defined in HsPat

type XNPlusKPat GhcRn # 
Instance details

Defined in HsPat

type XNPlusKPat GhcPs # 
Instance details

Defined in HsPat

type XNPat GhcTc # 
Instance details

Defined in HsPat

type XNPat GhcRn # 
Instance details

Defined in HsPat

type XNPat GhcPs # 
Instance details

Defined in HsPat

type XViewPat GhcTc # 
Instance details

Defined in HsPat

type XViewPat GhcRn # 
Instance details

Defined in HsPat

type XViewPat GhcPs # 
Instance details

Defined in HsPat

type XSumPat GhcTc # 
Instance details

Defined in HsPat

type XSumPat GhcTc = [Type]
type XSumPat GhcRn # 
Instance details

Defined in HsPat

type XSumPat GhcPs # 
Instance details

Defined in HsPat

type XTuplePat GhcTc # 
Instance details

Defined in HsPat

type XTuplePat GhcRn # 
Instance details

Defined in HsPat

type XTuplePat GhcPs # 
Instance details

Defined in HsPat

type XListPat GhcTc # 
Instance details

Defined in HsPat

type XListPat GhcRn # 
Instance details

Defined in HsPat

type XListPat GhcPs # 
Instance details

Defined in HsPat

type XWildPat GhcTc # 
Instance details

Defined in HsPat

type XWildPat GhcRn # 
Instance details

Defined in HsPat

type XWildPat GhcPs # 
Instance details

Defined in HsPat

type XOverLit GhcTc # 
Instance details

Defined in HsLit

type XOverLit GhcRn # 
Instance details

Defined in HsLit

type XOverLit GhcPs # 
Instance details

Defined in HsLit

type XCmdDo GhcTc # 
Instance details

Defined in HsExpr

type XCmdDo GhcRn # 
Instance details

Defined in HsExpr

type XCmdDo GhcPs # 
Instance details

Defined in HsExpr

type XCmdArrApp GhcTc # 
Instance details

Defined in HsExpr

type XCmdArrApp GhcRn # 
Instance details

Defined in HsExpr

type XCmdArrApp GhcPs # 
Instance details

Defined in HsExpr

type XCmdTop GhcTc # 
Instance details

Defined in HsExpr

type XCmdTop GhcRn # 
Instance details

Defined in HsExpr

type XCmdTop GhcPs # 
Instance details

Defined in HsExpr

type XMissing GhcTc # 
Instance details

Defined in HsExpr

type XMissing GhcRn # 
Instance details

Defined in HsExpr

type XMissing GhcPs # 
Instance details

Defined in HsExpr

type XAmbiguous GhcTc # 
Instance details

Defined in HsTypes

type XAmbiguous GhcRn # 
Instance details

Defined in HsTypes

type XAmbiguous GhcPs # 
Instance details

Defined in HsTypes

type XUnambiguous GhcTc # 
Instance details

Defined in HsTypes

type XUnambiguous GhcRn # 
Instance details

Defined in HsTypes

type XUnambiguous GhcPs # 
Instance details

Defined in HsTypes

type XArrApp GhcTc # 
Instance details

Defined in HsExpr

type XArrApp GhcRn # 
Instance details

Defined in HsExpr

type XArrApp GhcPs # 
Instance details

Defined in HsExpr

type XStatic GhcTc # 
Instance details

Defined in HsExpr

type XStatic GhcRn # 
Instance details

Defined in HsExpr

type XStatic GhcPs # 
Instance details

Defined in HsExpr

type XArithSeq GhcTc # 
Instance details

Defined in HsExpr

type XArithSeq GhcRn # 
Instance details

Defined in HsExpr

type XArithSeq GhcPs # 
Instance details

Defined in HsExpr

type XRecordUpd GhcTc # 
Instance details

Defined in HsExpr

type XRecordUpd GhcRn # 
Instance details

Defined in HsExpr

type XRecordUpd GhcPs # 
Instance details

Defined in HsExpr

type XRecordCon GhcTc # 
Instance details

Defined in HsExpr

type XRecordCon GhcRn # 
Instance details

Defined in HsExpr

type XRecordCon GhcPs # 
Instance details

Defined in HsExpr

type XExplicitList GhcTc # 
Instance details

Defined in HsExpr

type XExplicitList GhcRn # 
Instance details

Defined in HsExpr

type XExplicitList GhcPs # 
Instance details

Defined in HsExpr

type XDo GhcTc # 
Instance details

Defined in HsExpr

type XDo GhcTc = Type
type XDo GhcRn # 
Instance details

Defined in HsExpr

type XDo GhcRn = NoExt
type XDo GhcPs # 
Instance details

Defined in HsExpr

type XDo GhcPs = NoExt
type XMultiIf GhcTc # 
Instance details

Defined in HsExpr

type XMultiIf GhcRn # 
Instance details

Defined in HsExpr

type XMultiIf GhcPs # 
Instance details

Defined in HsExpr

type XExplicitSum GhcTc # 
Instance details

Defined in HsExpr

type XExplicitSum GhcRn # 
Instance details

Defined in HsExpr

type XExplicitSum GhcPs # 
Instance details

Defined in HsExpr

type XOpApp GhcTc # 
Instance details

Defined in HsExpr

type XOpApp GhcRn # 
Instance details

Defined in HsExpr

type XOpApp GhcPs # 
Instance details

Defined in HsExpr

type XHsRule GhcTc # 
Instance details

Defined in HsDecls

type XHsRule GhcRn # 
Instance details

Defined in HsDecls

type XHsRule GhcPs # 
Instance details

Defined in HsDecls

type XForeignExport GhcTc # 
Instance details

Defined in HsDecls

type XForeignExport GhcRn # 
Instance details

Defined in HsDecls

type XForeignExport GhcPs # 
Instance details

Defined in HsDecls

type XForeignImport GhcTc # 
Instance details

Defined in HsDecls

type XForeignImport GhcRn # 
Instance details

Defined in HsDecls

type XForeignImport GhcPs # 
Instance details

Defined in HsDecls

type XViaStrategy GhcTc # 
Instance details

Defined in HsDecls

type XViaStrategy GhcRn # 
Instance details

Defined in HsDecls

type XViaStrategy GhcPs # 
Instance details

Defined in HsDecls

type XClassDecl GhcTc # 
Instance details

Defined in HsDecls

type XClassDecl GhcRn # 
Instance details

Defined in HsDecls

type XClassDecl GhcPs # 
Instance details

Defined in HsDecls

type XDataDecl GhcTc # 
Instance details

Defined in HsDecls

type XDataDecl GhcRn # 
Instance details

Defined in HsDecls

type XDataDecl GhcPs # 
Instance details

Defined in HsDecls

type XSynDecl GhcTc # 
Instance details

Defined in HsDecls

type XSynDecl GhcRn # 
Instance details

Defined in HsDecls

type XSynDecl GhcPs # 
Instance details

Defined in HsDecls

type XIPBinds GhcTc # 
Instance details

Defined in HsBinds

type XIPBinds GhcRn # 
Instance details

Defined in HsBinds

type XIPBinds GhcPs # 
Instance details

Defined in HsBinds

type IdP GhcTc # 
Instance details

Defined in HsExtension

type IdP GhcTc = Id
type IdP GhcRn # 
Instance details

Defined in HsExtension

type IdP GhcRn = Name
type IdP GhcPs # 
Instance details

Defined in HsExtension

type XHsWC GhcTc b # 
Instance details

Defined in HsTypes

type XHsWC GhcTc b = [Name]
type XHsWC GhcRn b # 
Instance details

Defined in HsTypes

type XHsWC GhcRn b = [Name]
type XHsWC GhcPs b # 
Instance details

Defined in HsTypes

type XHsWC GhcPs b = NoExt
type XHsIB GhcTc _1 # 
Instance details

Defined in HsTypes

type XHsIB GhcTc _1 = [Name]
type XHsIB GhcRn _1 # 
Instance details

Defined in HsTypes

type XHsIB GhcRn _1 = [Name]
type XHsIB GhcPs _1 # 
Instance details

Defined in HsTypes

type XHsIB GhcPs _1 = NoExt
type XMG GhcTc b # 
Instance details

Defined in HsExpr

type XMG GhcRn b # 
Instance details

Defined in HsExpr

type XMG GhcRn b = NoExt
type XMG GhcPs b # 
Instance details

Defined in HsExpr

type XMG GhcPs b = NoExt
type XPatBind GhcTc (GhcPass pR) # 
Instance details

Defined in HsBinds

type XPatBind GhcRn (GhcPass pR) # 
Instance details

Defined in HsBinds

type XPatBind GhcPs (GhcPass pR) # 
Instance details

Defined in HsBinds

type SrcSpanLess (LPat (GhcPass p)) # 
Instance details

Defined in HsPat

type XXIE (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XXIE (GhcPass _1) = NoExt
type XIEDocNamed (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEDoc (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEDoc (GhcPass _1) = NoExt
type XIEGroup (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEGroup (GhcPass _1) = NoExt
type XIEModuleContents (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEThingWith (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEThingAll (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEThingAbs (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEVar (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEVar (GhcPass _1) = NoExt
type XXImportDecl (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XCImportDecl (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XXFieldOcc (GhcPass _1) # 
Instance details

Defined in HsTypes

type XXConDeclField (GhcPass _1) # 
Instance details

Defined in HsTypes

type XConDeclField (GhcPass _1) # 
Instance details

Defined in HsTypes

type XXTyVarBndr (GhcPass _1) # 
Instance details

Defined in HsTypes

type XKindedTyVar (GhcPass _1) # 
Instance details

Defined in HsTypes

type XUserTyVar (GhcPass _1) # 
Instance details

Defined in HsTypes

type XXType (GhcPass _1) # 
Instance details

Defined in HsTypes

type XWildCardTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XTyLit (GhcPass _1) # 
Instance details

Defined in HsTypes

type XTyLit (GhcPass _1) = NoExt
type XRecTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XRecTy (GhcPass _1) = NoExt
type XBangTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XBangTy (GhcPass _1) = NoExt
type XDocTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XDocTy (GhcPass _1) = NoExt
type XKindSig (GhcPass _1) # 
Instance details

Defined in HsTypes

type XKindSig (GhcPass _1) = NoExt
type XStarTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XStarTy (GhcPass _1) = NoExt
type XIParamTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XIParamTy (GhcPass _1) = NoExt
type XParTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XParTy (GhcPass _1) = NoExt
type XOpTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XOpTy (GhcPass _1) = NoExt
type XSumTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XSumTy (GhcPass _1) = NoExt
type XTupleTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XTupleTy (GhcPass _1) = NoExt
type XListTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XListTy (GhcPass _1) = NoExt
type XFunTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XFunTy (GhcPass _1) = NoExt
type XAppKindTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XAppTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XAppTy (GhcPass _1) = NoExt
type XTyVar (GhcPass _1) # 
Instance details

Defined in HsTypes

type XTyVar (GhcPass _1) = NoExt
type XQualTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XQualTy (GhcPass _1) = NoExt
type XForAllTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XForAllTy (GhcPass _1) = NoExt
type XXLHsQTyVars (GhcPass _1) # 
Instance details

Defined in HsTypes

type XXPat (GhcPass p) # 
Instance details

Defined in HsPat

type XXPat (GhcPass p) = Located (Pat (GhcPass p))
type XCoPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XCoPat (GhcPass _1) = NoExt
type XLitPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XLitPat (GhcPass _1) = NoExt
type XSplicePat (GhcPass _1) # 
Instance details

Defined in HsPat

type XBangPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XBangPat (GhcPass _1) = NoExt
type XParPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XParPat (GhcPass _1) = NoExt
type XAsPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XAsPat (GhcPass _1) = NoExt
type XLazyPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XLazyPat (GhcPass _1) = NoExt
type XVarPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XVarPat (GhcPass _1) = NoExt
type XXOverLit (GhcPass _1) # 
Instance details

Defined in HsLit

type XXOverLit (GhcPass _1) = NoExt
type XXLit (GhcPass _1) # 
Instance details

Defined in HsLit

type XXLit (GhcPass _1) = NoExt
type XHsDoublePrim (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsFloatPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsRat (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsRat (GhcPass _1) = NoExt
type XHsInteger (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsWord64Prim (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsInt64Prim (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsWordPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsIntPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsInt (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsInt (GhcPass _1) = NoExt
type XHsStringPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsString (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsCharPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsChar (GhcPass _1) # 
Instance details

Defined in HsLit

type XXApplicativeArg (GhcPass _1) # 
Instance details

Defined in HsExpr

type XApplicativeArgMany (GhcPass _1) # 
Instance details

Defined in HsExpr

type XApplicativeArgOne (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXCmd (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXCmd (GhcPass _1) = NoExt
type XCmdWrap (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdWrap (GhcPass _1) = NoExt
type XCmdLet (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdLet (GhcPass _1) = NoExt
type XCmdIf (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdIf (GhcPass _1) = NoExt
type XCmdCase (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdCase (GhcPass _1) = NoExt
type XCmdPar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdPar (GhcPass _1) = NoExt
type XCmdLam (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdLam (GhcPass _1) = NoExt
type XCmdApp (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdApp (GhcPass _1) = NoExt
type XCmdArrForm (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXCmdTop (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXCmdTop (GhcPass _1) = NoExt
type XXBracket (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXBracket (GhcPass _1) = NoExt
type XTExpBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XTExpBr (GhcPass _1) = NoExt
type XVarBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XVarBr (GhcPass _1) = NoExt
type XTypBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XTypBr (GhcPass _1) = NoExt
type XDecBrG (GhcPass _1) # 
Instance details

Defined in HsExpr

type XDecBrG (GhcPass _1) = NoExt
type XDecBrL (GhcPass _1) # 
Instance details

Defined in HsExpr

type XDecBrL (GhcPass _1) = NoExt
type XPatBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XPatBr (GhcPass _1) = NoExt
type XExpBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XExpBr (GhcPass _1) = NoExt
type XXSplice (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXSplice (GhcPass _1) = NoExt
type XSpliced (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSpliced (GhcPass _1) = NoExt
type XQuasiQuote (GhcPass _1) # 
Instance details

Defined in HsExpr

type XUntypedSplice (GhcPass _1) # 
Instance details

Defined in HsExpr

type XTypedSplice (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXTupArg (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXTupArg (GhcPass _1) = NoExt
type XPresent (GhcPass _1) # 
Instance details

Defined in HsExpr

type XPresent (GhcPass _1) = NoExt
type XXAmbiguousFieldOcc (GhcPass _1) # 
Instance details

Defined in HsTypes

type XXExpr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXExpr (GhcPass _1) = NoExt
type XWrap (GhcPass _1) # 
Instance details

Defined in HsExpr

type XWrap (GhcPass _1) = NoExt
type XELazyPat (GhcPass _1) # 
Instance details

Defined in HsExpr

type XELazyPat (GhcPass _1) = NoExt
type XEViewPat (GhcPass _1) # 
Instance details

Defined in HsExpr

type XEViewPat (GhcPass _1) = NoExt
type XEAsPat (GhcPass _1) # 
Instance details

Defined in HsExpr

type XEAsPat (GhcPass _1) = NoExt
type XEWildPat (GhcPass _1) # 
Instance details

Defined in HsExpr

type XEWildPat (GhcPass _1) = NoExt
type XTickPragma (GhcPass _1) # 
Instance details

Defined in HsExpr

type XBinTick (GhcPass _1) # 
Instance details

Defined in HsExpr

type XBinTick (GhcPass _1) = NoExt
type XTick (GhcPass _1) # 
Instance details

Defined in HsExpr

type XTick (GhcPass _1) = NoExt
type XArrForm (GhcPass _1) # 
Instance details

Defined in HsExpr

type XArrForm (GhcPass _1) = NoExt
type XProc (GhcPass _1) # 
Instance details

Defined in HsExpr

type XProc (GhcPass _1) = NoExt
type XSpliceE (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSpliceE (GhcPass _1) = NoExt
type XTcBracketOut (GhcPass _1) # 
Instance details

Defined in HsExpr

type XRnBracketOut (GhcPass _1) # 
Instance details

Defined in HsExpr

type XBracket (GhcPass _1) # 
Instance details

Defined in HsExpr

type XBracket (GhcPass _1) = NoExt
type XCoreAnn (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCoreAnn (GhcPass _1) = NoExt
type XSCC (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSCC (GhcPass _1) = NoExt
type XExprWithTySig (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLet (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLet (GhcPass _1) = NoExt
type XIf (GhcPass _1) # 
Instance details

Defined in HsExpr

type XIf (GhcPass _1) = NoExt
type XCase (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCase (GhcPass _1) = NoExt
type XExplicitTuple (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSectionR (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSectionR (GhcPass _1) = NoExt
type XSectionL (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSectionL (GhcPass _1) = NoExt
type XPar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XPar (GhcPass _1) = NoExt
type XNegApp (GhcPass _1) # 
Instance details

Defined in HsExpr

type XNegApp (GhcPass _1) = NoExt
type XAppTypeE (GhcPass _1) # 
Instance details

Defined in HsExpr

type XAppTypeE (GhcPass _1) = NoExt
type XApp (GhcPass _1) # 
Instance details

Defined in HsExpr

type XApp (GhcPass _1) = NoExt
type XLamCase (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLamCase (GhcPass _1) = NoExt
type XLam (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLam (GhcPass _1) = NoExt
type XLitE (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLitE (GhcPass _1) = NoExt
type XOverLitE (GhcPass _1) # 
Instance details

Defined in HsExpr

type XOverLitE (GhcPass _1) = NoExt
type XIPVar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XIPVar (GhcPass _1) = NoExt
type XOverLabel (GhcPass _1) # 
Instance details

Defined in HsExpr

type XRecFld (GhcPass _1) # 
Instance details

Defined in HsExpr

type XRecFld (GhcPass _1) = NoExt
type XConLikeOut (GhcPass _1) # 
Instance details

Defined in HsExpr

type XUnboundVar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XVar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XVar (GhcPass _1) = NoExt
type XXRoleAnnotDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCRoleAnnotDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXAnnDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXAnnDecl (GhcPass _1) = NoExt
type XHsAnnotation (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXWarnDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XWarning (GhcPass _1) # 
Instance details

Defined in HsDecls

type XWarning (GhcPass _1) = NoExt
type XXWarnDecls (GhcPass _1) # 
Instance details

Defined in HsDecls

type XWarnings (GhcPass _1) # 
Instance details

Defined in HsDecls

type XWarnings (GhcPass _1) = NoExt
type XXRuleBndr (GhcPass _1) # 
Instance details

Defined in HsDecls

type XRuleBndrSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCRuleBndr (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXRuleDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXRuleDecls (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCRuleDecls (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXForeignDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXDefaultDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCDefaultDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXDerivDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCDerivDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXInstDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XTyFamInstD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XDataFamInstD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XClsInstD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XClsInstD (GhcPass _1) = NoExt
type XXClsInstDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCClsInstDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXConDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXConDecl (GhcPass _1) = NoExt
type XConDeclH98 (GhcPass _1) # 
Instance details

Defined in HsDecls

type XConDeclGADT (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXHsDerivingClause (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCHsDerivingClause (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXHsDataDefn (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCHsDataDefn (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXFamilyDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCFamilyDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXFamilyResultSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type XTyVarSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type XTyVarSig (GhcPass _1) = NoExt
type XCKindSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCKindSig (GhcPass _1) = NoExt
type XNoSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type XNoSig (GhcPass _1) = NoExt
type XXTyClGroup (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCTyClGroup (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXTyClDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XFamDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XFamDecl (GhcPass _1) = NoExt
type XXSpliceDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XSpliceDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXHsGroup (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXHsGroup (GhcPass _1) = NoExt
type XCHsGroup (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCHsGroup (GhcPass _1) = NoExt
type XXHsDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXHsDecl (GhcPass _1) = NoExt
type XRoleAnnotD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XDocD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XDocD (GhcPass _1) = NoExt
type XSpliceD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XSpliceD (GhcPass _1) = NoExt
type XRuleD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XRuleD (GhcPass _1) = NoExt
type XAnnD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XAnnD (GhcPass _1) = NoExt
type XWarningD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XWarningD (GhcPass _1) = NoExt
type XForD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XForD (GhcPass _1) = NoExt
type XDefD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XDefD (GhcPass _1) = NoExt
type XSigD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XSigD (GhcPass _1) = NoExt
type XValD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XValD (GhcPass _1) = NoExt
type XDerivD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XDerivD (GhcPass _1) = NoExt
type XInstD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XInstD (GhcPass _1) = NoExt
type XTyClD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XTyClD (GhcPass _1) = NoExt
type XXFixitySig (GhcPass p) # 
Instance details

Defined in HsBinds

type XFixitySig (GhcPass p) # 
Instance details

Defined in HsBinds

type XXSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XXSig (GhcPass p) = NoExt
type XCompleteMatchSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XSCCFunSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XMinimalSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XSpecInstSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XSpecSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XInlineSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XFixSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XFixSig (GhcPass p) = NoExt
type XIdSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XIdSig (GhcPass p) = NoExt
type XClassOpSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XPatSynSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XTypeSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XXIPBind (GhcPass p) # 
Instance details

Defined in HsBinds

type XCIPBind (GhcPass p) # 
Instance details

Defined in HsBinds

type XXHsIPBinds (GhcPass p) # 
Instance details

Defined in HsBinds

type XXABExport (GhcPass p) # 
Instance details

Defined in HsBinds

type XABE (GhcPass p) # 
Instance details

Defined in HsBinds

type XABE (GhcPass p) = NoExt
type XXHsWildCardBndrs (GhcPass _1) b # 
Instance details

Defined in HsTypes

type XXHsImplicitBndrs (GhcPass _1) _2 # 
Instance details

Defined in HsTypes

type XXGRHS (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XXGRHS (GhcPass _1) b = NoExt
type XCGRHS (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XCGRHS (GhcPass _1) b = NoExt
type XXGRHSs (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XXGRHSs (GhcPass _1) b = NoExt
type XCGRHSs (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XCGRHSs (GhcPass _1) b = NoExt
type XXMatch (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XXMatch (GhcPass _1) b = NoExt
type XCMatch (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XCMatch (GhcPass _1) b = NoExt
type XXMatchGroup (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XXMatchGroup (GhcPass _1) b = NoExt
type XPSB (GhcPass idL) GhcTc # 
Instance details

Defined in HsBinds

type XPSB (GhcPass idL) GhcTc = NameSet
type XPSB (GhcPass idL) GhcRn # 
Instance details

Defined in HsBinds

type XPSB (GhcPass idL) GhcRn = NameSet
type XPSB (GhcPass idL) GhcPs # 
Instance details

Defined in HsBinds

type XPSB (GhcPass idL) GhcPs = NoExt
type XFunBind (GhcPass pL) GhcTc # 
Instance details

Defined in HsBinds

type XFunBind (GhcPass pL) GhcRn # 
Instance details

Defined in HsBinds

type XFunBind (GhcPass pL) GhcPs # 
Instance details

Defined in HsBinds

type XRecStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XRecStmt (GhcPass _1) GhcRn b = NoExt
type XRecStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type XRecStmt (GhcPass _1) GhcPs b = NoExt
type XRecStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XTransStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XTransStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XTransStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type XParStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XParStmt (GhcPass _1) GhcTc b = Type
type XParStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XParStmt (GhcPass _1) GhcRn b = NoExt
type XParStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type XParStmt (GhcPass _1) GhcPs b = NoExt
type XBodyStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XBodyStmt (GhcPass _1) GhcTc b = Type
type XBodyStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XBodyStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type XApplicativeStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XApplicativeStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XApplicativeStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type XBindStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XBindStmt (GhcPass _1) GhcTc b = Type
type XBindStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XBindStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type XXFamEqn (GhcPass _1) p r # 
Instance details

Defined in HsDecls

type XXFamEqn (GhcPass _1) p r = NoExt
type XCFamEqn (GhcPass _1) p r # 
Instance details

Defined in HsDecls

type XCFamEqn (GhcPass _1) p r = NoExt
type XXParStmtBlock (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsExpr

type XParStmtBlock (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsExpr

type XXPatSynBind (GhcPass idL) (GhcPass idR) # 
Instance details

Defined in HsBinds

type XXPatSynBind (GhcPass idL) (GhcPass idR) = NoExt
type XXHsBindsLR (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XXHsBindsLR (GhcPass pL) (GhcPass pR) = NoExt
type XPatSynBind (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XPatSynBind (GhcPass pL) (GhcPass pR) = NoExt
type XAbsBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XAbsBinds (GhcPass pL) (GhcPass pR) = NoExt
type XVarBind (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XVarBind (GhcPass pL) (GhcPass pR) = NoExt
type XXValBindsLR (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XValBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XValBinds (GhcPass pL) (GhcPass pR) = NoExt
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XHsIPBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XHsIPBinds (GhcPass pL) (GhcPass pR) = NoExt
type XHsValBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XHsValBinds (GhcPass pL) (GhcPass pR) = NoExt
type XXStmtLR (GhcPass _1) (GhcPass _2) b # 
Instance details

Defined in HsExpr

type XXStmtLR (GhcPass _1) (GhcPass _2) b = NoExt
type XLetStmt (GhcPass _1) (GhcPass _2) b # 
Instance details

Defined in HsExpr

type XLetStmt (GhcPass _1) (GhcPass _2) b = NoExt
type XLastStmt (GhcPass _1) (GhcPass _2) b # 
Instance details

Defined in HsExpr

type XLastStmt (GhcPass _1) (GhcPass _2) b = NoExt

data Pass Source #

Constructors

Parsed 
Renamed 
Typechecked 

Instances

Instances details
Data Pass # 
Instance details

Defined in HsExtension

Methods

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

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

toConstr :: Pass -> Constr Source #

dataTypeOf :: Pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

type family IdP p Source #

Maps the "normal" id type for a given pass

Instances

Instances details
type IdP GhcTc # 
Instance details

Defined in HsExtension

type IdP GhcTc = Id
type IdP GhcRn # 
Instance details

Defined in HsExtension

type IdP GhcRn = Name
type IdP GhcPs # 
Instance details

Defined in HsExtension

type LIdP p = Located (IdP p) Source #

type family NoGhcTc (p :: Type) where ... Source #

Marks that a field uses the GhcRn variant even when the pass parameter is GhcTc. Useful for storing HsTypes in HsExprs, say, because HsType GhcTc should never occur.

Equations

NoGhcTc (GhcPass pass) = GhcPass (NoGhcTcPass pass) 
NoGhcTc other = other 

type family NoGhcTcPass (p :: Pass) :: Pass where ... Source #

Equations

NoGhcTcPass 'Typechecked = 'Renamed 
NoGhcTcPass other = other 

type family XHsValBinds x x' Source #

Instances

Instances details
type XHsValBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XHsValBinds (GhcPass pL) (GhcPass pR) = NoExt

type family XHsIPBinds x x' Source #

Instances

Instances details
type XHsIPBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XHsIPBinds (GhcPass pL) (GhcPass pR) = NoExt

type family XEmptyLocalBinds x x' Source #

Instances

Instances details
type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type family XXHsLocalBindsLR x x' Source #

Instances

Instances details
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type ForallXHsLocalBindsLR (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XHsValBinds x x'), c (XHsIPBinds x x'), c (XEmptyLocalBinds x x'), c (XXHsLocalBindsLR x x')) Source #

type family XValBinds x x' Source #

Instances

Instances details
type XValBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XValBinds (GhcPass pL) (GhcPass pR) = NoExt

type family XXValBindsLR x x' Source #

Instances

Instances details
type XXValBindsLR (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type ForallXValBindsLR (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XValBinds x x'), c (XXValBindsLR x x')) Source #

type family XFunBind x x' Source #

Instances

Instances details
type XFunBind (GhcPass pL) GhcTc # 
Instance details

Defined in HsBinds

type XFunBind (GhcPass pL) GhcRn # 
Instance details

Defined in HsBinds

type XFunBind (GhcPass pL) GhcPs # 
Instance details

Defined in HsBinds

type family XPatBind x x' Source #

Instances

Instances details
type XPatBind GhcTc (GhcPass pR) # 
Instance details

Defined in HsBinds

type XPatBind GhcRn (GhcPass pR) # 
Instance details

Defined in HsBinds

type XPatBind GhcPs (GhcPass pR) # 
Instance details

Defined in HsBinds

type family XVarBind x x' Source #

Instances

Instances details
type XVarBind (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XVarBind (GhcPass pL) (GhcPass pR) = NoExt

type family XAbsBinds x x' Source #

Instances

Instances details
type XAbsBinds (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XAbsBinds (GhcPass pL) (GhcPass pR) = NoExt

type family XPatSynBind x x' Source #

Instances

Instances details
type XPatSynBind (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XPatSynBind (GhcPass pL) (GhcPass pR) = NoExt

type family XXHsBindsLR x x' Source #

Instances

Instances details
type XXHsBindsLR (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsBinds

type XXHsBindsLR (GhcPass pL) (GhcPass pR) = NoExt

type ForallXHsBindsLR (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XFunBind x x'), c (XPatBind x x'), c (XVarBind x x'), c (XAbsBinds x x'), c (XPatSynBind x x'), c (XXHsBindsLR x x')) Source #

type family XABE x Source #

Instances

Instances details
type XABE (GhcPass p) # 
Instance details

Defined in HsBinds

type XABE (GhcPass p) = NoExt

type family XXABExport x Source #

Instances

Instances details
type XXABExport (GhcPass p) # 
Instance details

Defined in HsBinds

type ForallXABExport (c :: * -> Constraint) (x :: *) = (c (XABE x), c (XXABExport x)) Source #

type family XPSB x x' Source #

Instances

Instances details
type XPSB (GhcPass idL) GhcTc # 
Instance details

Defined in HsBinds

type XPSB (GhcPass idL) GhcTc = NameSet
type XPSB (GhcPass idL) GhcRn # 
Instance details

Defined in HsBinds

type XPSB (GhcPass idL) GhcRn = NameSet
type XPSB (GhcPass idL) GhcPs # 
Instance details

Defined in HsBinds

type XPSB (GhcPass idL) GhcPs = NoExt

type family XXPatSynBind x x' Source #

Instances

Instances details
type XXPatSynBind (GhcPass idL) (GhcPass idR) # 
Instance details

Defined in HsBinds

type XXPatSynBind (GhcPass idL) (GhcPass idR) = NoExt

type ForallXPatSynBind (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XPSB x x'), c (XXPatSynBind x x')) Source #

type family XIPBinds x Source #

Instances

Instances details
type XIPBinds GhcTc # 
Instance details

Defined in HsBinds

type XIPBinds GhcRn # 
Instance details

Defined in HsBinds

type XIPBinds GhcPs # 
Instance details

Defined in HsBinds

type family XXHsIPBinds x Source #

Instances

Instances details
type XXHsIPBinds (GhcPass p) # 
Instance details

Defined in HsBinds

type ForallXHsIPBinds (c :: * -> Constraint) (x :: *) = (c (XIPBinds x), c (XXHsIPBinds x)) Source #

type family XCIPBind x Source #

Instances

Instances details
type XCIPBind (GhcPass p) # 
Instance details

Defined in HsBinds

type family XXIPBind x Source #

Instances

Instances details
type XXIPBind (GhcPass p) # 
Instance details

Defined in HsBinds

type ForallXIPBind (c :: * -> Constraint) (x :: *) = (c (XCIPBind x), c (XXIPBind x)) Source #

type family XTypeSig x Source #

Instances

Instances details
type XTypeSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XPatSynSig x Source #

Instances

Instances details
type XPatSynSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XClassOpSig x Source #

Instances

Instances details
type XClassOpSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XIdSig x Source #

Instances

Instances details
type XIdSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XIdSig (GhcPass p) = NoExt

type family XFixSig x Source #

Instances

Instances details
type XFixSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XFixSig (GhcPass p) = NoExt

type family XInlineSig x Source #

Instances

Instances details
type XInlineSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XSpecSig x Source #

Instances

Instances details
type XSpecSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XSpecInstSig x Source #

Instances

Instances details
type XSpecInstSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XMinimalSig x Source #

Instances

Instances details
type XMinimalSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XSCCFunSig x Source #

Instances

Instances details
type XSCCFunSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XCompleteMatchSig x Source #

Instances

Instances details
type XCompleteMatchSig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XXSig x Source #

Instances

Instances details
type XXSig (GhcPass p) # 
Instance details

Defined in HsBinds

type XXSig (GhcPass p) = NoExt

type ForallXSig (c :: * -> Constraint) (x :: *) = (c (XTypeSig x), c (XPatSynSig x), c (XClassOpSig x), c (XIdSig x), c (XFixSig x), c (XInlineSig x), c (XSpecSig x), c (XSpecInstSig x), c (XMinimalSig x), c (XSCCFunSig x), c (XCompleteMatchSig x), c (XXSig x)) Source #

type family XFixitySig x Source #

Instances

Instances details
type XFixitySig (GhcPass p) # 
Instance details

Defined in HsBinds

type family XXFixitySig x Source #

Instances

Instances details
type XXFixitySig (GhcPass p) # 
Instance details

Defined in HsBinds

type ForallXFixitySig (c :: * -> Constraint) (x :: *) = (c (XFixitySig x), c (XXFixitySig x)) Source #

type family XTyClD x Source #

Instances

Instances details
type XTyClD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XTyClD (GhcPass _1) = NoExt

type family XInstD x Source #

Instances

Instances details
type XInstD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XInstD (GhcPass _1) = NoExt

type family XDerivD x Source #

Instances

Instances details
type XDerivD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XDerivD (GhcPass _1) = NoExt

type family XValD x Source #

Instances

Instances details
type XValD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XValD (GhcPass _1) = NoExt

type family XSigD x Source #

Instances

Instances details
type XSigD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XSigD (GhcPass _1) = NoExt

type family XDefD x Source #

Instances

Instances details
type XDefD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XDefD (GhcPass _1) = NoExt

type family XForD x Source #

Instances

Instances details
type XForD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XForD (GhcPass _1) = NoExt

type family XWarningD x Source #

Instances

Instances details
type XWarningD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XWarningD (GhcPass _1) = NoExt

type family XAnnD x Source #

Instances

Instances details
type XAnnD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XAnnD (GhcPass _1) = NoExt

type family XRuleD x Source #

Instances

Instances details
type XRuleD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XRuleD (GhcPass _1) = NoExt

type family XSpliceD x Source #

Instances

Instances details
type XSpliceD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XSpliceD (GhcPass _1) = NoExt

type family XDocD x Source #

Instances

Instances details
type XDocD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XDocD (GhcPass _1) = NoExt

type family XRoleAnnotD x Source #

Instances

Instances details
type XRoleAnnotD (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXHsDecl x Source #

Instances

Instances details
type XXHsDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXHsDecl (GhcPass _1) = NoExt

type ForallXHsDecl (c :: * -> Constraint) (x :: *) = (c (XTyClD x), c (XInstD x), c (XDerivD x), c (XValD x), c (XSigD x), c (XDefD x), c (XForD x), c (XWarningD x), c (XAnnD x), c (XRuleD x), c (XSpliceD x), c (XDocD x), c (XRoleAnnotD x), c (XXHsDecl x)) Source #

type family XCHsGroup x Source #

Instances

Instances details
type XCHsGroup (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCHsGroup (GhcPass _1) = NoExt

type family XXHsGroup x Source #

Instances

Instances details
type XXHsGroup (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXHsGroup (GhcPass _1) = NoExt

type ForallXHsGroup (c :: * -> Constraint) (x :: *) = (c (XCHsGroup x), c (XXHsGroup x)) Source #

type family XSpliceDecl x Source #

Instances

Instances details
type XSpliceDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXSpliceDecl x Source #

Instances

Instances details
type XXSpliceDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXSpliceDecl (c :: * -> Constraint) (x :: *) = (c (XSpliceDecl x), c (XXSpliceDecl x)) Source #

type family XFamDecl x Source #

Instances

Instances details
type XFamDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XFamDecl (GhcPass _1) = NoExt

type family XSynDecl x Source #

Instances

Instances details
type XSynDecl GhcTc # 
Instance details

Defined in HsDecls

type XSynDecl GhcRn # 
Instance details

Defined in HsDecls

type XSynDecl GhcPs # 
Instance details

Defined in HsDecls

type family XDataDecl x Source #

Instances

Instances details
type XDataDecl GhcTc # 
Instance details

Defined in HsDecls

type XDataDecl GhcRn # 
Instance details

Defined in HsDecls

type XDataDecl GhcPs # 
Instance details

Defined in HsDecls

type family XClassDecl x Source #

Instances

Instances details
type XClassDecl GhcTc # 
Instance details

Defined in HsDecls

type XClassDecl GhcRn # 
Instance details

Defined in HsDecls

type XClassDecl GhcPs # 
Instance details

Defined in HsDecls

type family XXTyClDecl x Source #

Instances

Instances details
type XXTyClDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXTyClDecl (c :: * -> Constraint) (x :: *) = (c (XFamDecl x), c (XSynDecl x), c (XDataDecl x), c (XClassDecl x), c (XXTyClDecl x)) Source #

type family XCTyClGroup x Source #

Instances

Instances details
type XCTyClGroup (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXTyClGroup x Source #

Instances

Instances details
type XXTyClGroup (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXTyClGroup (c :: * -> Constraint) (x :: *) = (c (XCTyClGroup x), c (XXTyClGroup x)) Source #

type family XNoSig x Source #

Instances

Instances details
type XNoSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type XNoSig (GhcPass _1) = NoExt

type family XCKindSig x Source #

Instances

Instances details
type XCKindSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type XCKindSig (GhcPass _1) = NoExt

type family XTyVarSig x Source #

Instances

Instances details
type XTyVarSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type XTyVarSig (GhcPass _1) = NoExt

type family XXFamilyResultSig x Source #

Instances

Instances details
type XXFamilyResultSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXFamilyResultSig (c :: * -> Constraint) (x :: *) = (c (XNoSig x), c (XCKindSig x), c (XTyVarSig x), c (XXFamilyResultSig x)) Source #

type family XCFamilyDecl x Source #

Instances

Instances details
type XCFamilyDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXFamilyDecl x Source #

Instances

Instances details
type XXFamilyDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXFamilyDecl (c :: * -> Constraint) (x :: *) = (c (XCFamilyDecl x), c (XXFamilyDecl x)) Source #

type family XCHsDataDefn x Source #

Instances

Instances details
type XCHsDataDefn (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXHsDataDefn x Source #

Instances

Instances details
type XXHsDataDefn (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXHsDataDefn (c :: * -> Constraint) (x :: *) = (c (XCHsDataDefn x), c (XXHsDataDefn x)) Source #

type family XCHsDerivingClause x Source #

Instances

Instances details
type XCHsDerivingClause (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXHsDerivingClause x Source #

Instances

Instances details
type XXHsDerivingClause (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XConDeclGADT x Source #

Instances

Instances details
type XConDeclGADT (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XConDeclH98 x Source #

Instances

Instances details
type XConDeclH98 (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXConDecl x Source #

Instances

Instances details
type XXConDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXConDecl (GhcPass _1) = NoExt

type ForallXConDecl (c :: * -> Constraint) (x :: *) = (c (XConDeclGADT x), c (XConDeclH98 x), c (XXConDecl x)) Source #

type family XCFamEqn x p r Source #

Instances

Instances details
type XCFamEqn (GhcPass _1) p r # 
Instance details

Defined in HsDecls

type XCFamEqn (GhcPass _1) p r = NoExt

type family XXFamEqn x p r Source #

Instances

Instances details
type XXFamEqn (GhcPass _1) p r # 
Instance details

Defined in HsDecls

type XXFamEqn (GhcPass _1) p r = NoExt

type ForallXFamEqn (c :: * -> Constraint) (x :: *) (p :: *) (r :: *) = (c (XCFamEqn x p r), c (XXFamEqn x p r)) Source #

type family XCClsInstDecl x Source #

Instances

Instances details
type XCClsInstDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXClsInstDecl x Source #

Instances

Instances details
type XXClsInstDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXClsInstDecl (c :: * -> Constraint) (x :: *) = (c (XCClsInstDecl x), c (XXClsInstDecl x)) Source #

type family XClsInstD x Source #

Instances

Instances details
type XClsInstD (GhcPass _1) # 
Instance details

Defined in HsDecls

type XClsInstD (GhcPass _1) = NoExt

type family XDataFamInstD x Source #

Instances

Instances details
type XDataFamInstD (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XTyFamInstD x Source #

Instances

Instances details
type XTyFamInstD (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXInstDecl x Source #

Instances

Instances details
type XXInstDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXInstDecl (c :: * -> Constraint) (x :: *) = (c (XClsInstD x), c (XDataFamInstD x), c (XTyFamInstD x), c (XXInstDecl x)) Source #

type family XCDerivDecl x Source #

Instances

Instances details
type XCDerivDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXDerivDecl x Source #

Instances

Instances details
type XXDerivDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXDerivDecl (c :: * -> Constraint) (x :: *) = (c (XCDerivDecl x), c (XXDerivDecl x)) Source #

type family XViaStrategy x Source #

Instances

Instances details
type XViaStrategy GhcTc # 
Instance details

Defined in HsDecls

type XViaStrategy GhcRn # 
Instance details

Defined in HsDecls

type XViaStrategy GhcPs # 
Instance details

Defined in HsDecls

type family XCDefaultDecl x Source #

Instances

Instances details
type XCDefaultDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXDefaultDecl x Source #

Instances

Instances details
type XXDefaultDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXDefaultDecl (c :: * -> Constraint) (x :: *) = (c (XCDefaultDecl x), c (XXDefaultDecl x)) Source #

type family XForeignImport x Source #

Instances

Instances details
type XForeignImport GhcTc # 
Instance details

Defined in HsDecls

type XForeignImport GhcRn # 
Instance details

Defined in HsDecls

type XForeignImport GhcPs # 
Instance details

Defined in HsDecls

type family XForeignExport x Source #

Instances

Instances details
type XForeignExport GhcTc # 
Instance details

Defined in HsDecls

type XForeignExport GhcRn # 
Instance details

Defined in HsDecls

type XForeignExport GhcPs # 
Instance details

Defined in HsDecls

type family XXForeignDecl x Source #

Instances

Instances details
type XXForeignDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXForeignDecl (c :: * -> Constraint) (x :: *) = (c (XForeignImport x), c (XForeignExport x), c (XXForeignDecl x)) Source #

type family XCRuleDecls x Source #

Instances

Instances details
type XCRuleDecls (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXRuleDecls x Source #

Instances

Instances details
type XXRuleDecls (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXRuleDecls (c :: * -> Constraint) (x :: *) = (c (XCRuleDecls x), c (XXRuleDecls x)) Source #

type family XHsRule x Source #

Instances

Instances details
type XHsRule GhcTc # 
Instance details

Defined in HsDecls

type XHsRule GhcRn # 
Instance details

Defined in HsDecls

type XHsRule GhcPs # 
Instance details

Defined in HsDecls

type family XXRuleDecl x Source #

Instances

Instances details
type XXRuleDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXRuleDecl (c :: * -> Constraint) (x :: *) = (c (XHsRule x), c (XXRuleDecl x)) Source #

type family XCRuleBndr x Source #

Instances

Instances details
type XCRuleBndr (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XRuleBndrSig x Source #

Instances

Instances details
type XRuleBndrSig (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXRuleBndr x Source #

Instances

Instances details
type XXRuleBndr (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXRuleBndr (c :: * -> Constraint) (x :: *) = (c (XCRuleBndr x), c (XRuleBndrSig x), c (XXRuleBndr x)) Source #

type family XWarnings x Source #

Instances

Instances details
type XWarnings (GhcPass _1) # 
Instance details

Defined in HsDecls

type XWarnings (GhcPass _1) = NoExt

type family XXWarnDecls x Source #

Instances

Instances details
type XXWarnDecls (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXWarnDecls (c :: * -> Constraint) (x :: *) = (c (XWarnings x), c (XXWarnDecls x)) Source #

type family XWarning x Source #

Instances

Instances details
type XWarning (GhcPass _1) # 
Instance details

Defined in HsDecls

type XWarning (GhcPass _1) = NoExt

type family XXWarnDecl x Source #

Instances

Instances details
type XXWarnDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXWarnDecl (c :: * -> Constraint) (x :: *) = (c (XWarning x), c (XXWarnDecl x)) Source #

type family XHsAnnotation x Source #

Instances

Instances details
type XHsAnnotation (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXAnnDecl x Source #

Instances

Instances details
type XXAnnDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type XXAnnDecl (GhcPass _1) = NoExt

type ForallXAnnDecl (c :: * -> Constraint) (x :: *) = (c (XHsAnnotation x), c (XXAnnDecl x)) Source #

type family XCRoleAnnotDecl x Source #

Instances

Instances details
type XCRoleAnnotDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type family XXRoleAnnotDecl x Source #

Instances

Instances details
type XXRoleAnnotDecl (GhcPass _1) # 
Instance details

Defined in HsDecls

type ForallXRoleAnnotDecl (c :: * -> Constraint) (x :: *) = (c (XCRoleAnnotDecl x), c (XXRoleAnnotDecl x)) Source #

type family XVar x Source #

Instances

Instances details
type XVar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XVar (GhcPass _1) = NoExt

type family XUnboundVar x Source #

Instances

Instances details
type XUnboundVar (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XConLikeOut x Source #

Instances

Instances details
type XConLikeOut (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XRecFld x Source #

Instances

Instances details
type XRecFld (GhcPass _1) # 
Instance details

Defined in HsExpr

type XRecFld (GhcPass _1) = NoExt

type family XOverLabel x Source #

Instances

Instances details
type XOverLabel (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XIPVar x Source #

Instances

Instances details
type XIPVar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XIPVar (GhcPass _1) = NoExt

type family XOverLitE x Source #

Instances

Instances details
type XOverLitE (GhcPass _1) # 
Instance details

Defined in HsExpr

type XOverLitE (GhcPass _1) = NoExt

type family XLitE x Source #

Instances

Instances details
type XLitE (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLitE (GhcPass _1) = NoExt

type family XLam x Source #

Instances

Instances details
type XLam (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLam (GhcPass _1) = NoExt

type family XLamCase x Source #

Instances

Instances details
type XLamCase (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLamCase (GhcPass _1) = NoExt

type family XApp x Source #

Instances

Instances details
type XApp (GhcPass _1) # 
Instance details

Defined in HsExpr

type XApp (GhcPass _1) = NoExt

type family XAppTypeE x Source #

Instances

Instances details
type XAppTypeE (GhcPass _1) # 
Instance details

Defined in HsExpr

type XAppTypeE (GhcPass _1) = NoExt

type family XOpApp x Source #

Instances

Instances details
type XOpApp GhcTc # 
Instance details

Defined in HsExpr

type XOpApp GhcRn # 
Instance details

Defined in HsExpr

type XOpApp GhcPs # 
Instance details

Defined in HsExpr

type family XNegApp x Source #

Instances

Instances details
type XNegApp (GhcPass _1) # 
Instance details

Defined in HsExpr

type XNegApp (GhcPass _1) = NoExt

type family XPar x Source #

Instances

Instances details
type XPar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XPar (GhcPass _1) = NoExt

type family XSectionL x Source #

Instances

Instances details
type XSectionL (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSectionL (GhcPass _1) = NoExt

type family XSectionR x Source #

Instances

Instances details
type XSectionR (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSectionR (GhcPass _1) = NoExt

type family XExplicitTuple x Source #

Instances

Instances details
type XExplicitTuple (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XExplicitSum x Source #

Instances

Instances details
type XExplicitSum GhcTc # 
Instance details

Defined in HsExpr

type XExplicitSum GhcRn # 
Instance details

Defined in HsExpr

type XExplicitSum GhcPs # 
Instance details

Defined in HsExpr

type family XCase x Source #

Instances

Instances details
type XCase (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCase (GhcPass _1) = NoExt

type family XIf x Source #

Instances

Instances details
type XIf (GhcPass _1) # 
Instance details

Defined in HsExpr

type XIf (GhcPass _1) = NoExt

type family XMultiIf x Source #

Instances

Instances details
type XMultiIf GhcTc # 
Instance details

Defined in HsExpr

type XMultiIf GhcRn # 
Instance details

Defined in HsExpr

type XMultiIf GhcPs # 
Instance details

Defined in HsExpr

type family XLet x Source #

Instances

Instances details
type XLet (GhcPass _1) # 
Instance details

Defined in HsExpr

type XLet (GhcPass _1) = NoExt

type family XDo x Source #

Instances

Instances details
type XDo GhcTc # 
Instance details

Defined in HsExpr

type XDo GhcTc = Type
type XDo GhcRn # 
Instance details

Defined in HsExpr

type XDo GhcRn = NoExt
type XDo GhcPs # 
Instance details

Defined in HsExpr

type XDo GhcPs = NoExt

type family XExplicitList x Source #

Instances

Instances details
type XExplicitList GhcTc # 
Instance details

Defined in HsExpr

type XExplicitList GhcRn # 
Instance details

Defined in HsExpr

type XExplicitList GhcPs # 
Instance details

Defined in HsExpr

type family XRecordCon x Source #

Instances

Instances details
type XRecordCon GhcTc # 
Instance details

Defined in HsExpr

type XRecordCon GhcRn # 
Instance details

Defined in HsExpr

type XRecordCon GhcPs # 
Instance details

Defined in HsExpr

type family XRecordUpd x Source #

Instances

Instances details
type XRecordUpd GhcTc # 
Instance details

Defined in HsExpr

type XRecordUpd GhcRn # 
Instance details

Defined in HsExpr

type XRecordUpd GhcPs # 
Instance details

Defined in HsExpr

type family XExprWithTySig x Source #

Instances

Instances details
type XExprWithTySig (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XArithSeq x Source #

Instances

Instances details
type XArithSeq GhcTc # 
Instance details

Defined in HsExpr

type XArithSeq GhcRn # 
Instance details

Defined in HsExpr

type XArithSeq GhcPs # 
Instance details

Defined in HsExpr

type family XSCC x Source #

Instances

Instances details
type XSCC (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSCC (GhcPass _1) = NoExt

type family XCoreAnn x Source #

Instances

Instances details
type XCoreAnn (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCoreAnn (GhcPass _1) = NoExt

type family XBracket x Source #

Instances

Instances details
type XBracket (GhcPass _1) # 
Instance details

Defined in HsExpr

type XBracket (GhcPass _1) = NoExt

type family XRnBracketOut x Source #

Instances

Instances details
type XRnBracketOut (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XTcBracketOut x Source #

Instances

Instances details
type XTcBracketOut (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XSpliceE x Source #

Instances

Instances details
type XSpliceE (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSpliceE (GhcPass _1) = NoExt

type family XProc x Source #

Instances

Instances details
type XProc (GhcPass _1) # 
Instance details

Defined in HsExpr

type XProc (GhcPass _1) = NoExt

type family XStatic x Source #

Instances

Instances details
type XStatic GhcTc # 
Instance details

Defined in HsExpr

type XStatic GhcRn # 
Instance details

Defined in HsExpr

type XStatic GhcPs # 
Instance details

Defined in HsExpr

type family XArrApp x Source #

Instances

Instances details
type XArrApp GhcTc # 
Instance details

Defined in HsExpr

type XArrApp GhcRn # 
Instance details

Defined in HsExpr

type XArrApp GhcPs # 
Instance details

Defined in HsExpr

type family XArrForm x Source #

Instances

Instances details
type XArrForm (GhcPass _1) # 
Instance details

Defined in HsExpr

type XArrForm (GhcPass _1) = NoExt

type family XTick x Source #

Instances

Instances details
type XTick (GhcPass _1) # 
Instance details

Defined in HsExpr

type XTick (GhcPass _1) = NoExt

type family XBinTick x Source #

Instances

Instances details
type XBinTick (GhcPass _1) # 
Instance details

Defined in HsExpr

type XBinTick (GhcPass _1) = NoExt

type family XTickPragma x Source #

Instances

Instances details
type XTickPragma (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XEWildPat x Source #

Instances

Instances details
type XEWildPat (GhcPass _1) # 
Instance details

Defined in HsExpr

type XEWildPat (GhcPass _1) = NoExt

type family XEAsPat x Source #

Instances

Instances details
type XEAsPat (GhcPass _1) # 
Instance details

Defined in HsExpr

type XEAsPat (GhcPass _1) = NoExt

type family XEViewPat x Source #

Instances

Instances details
type XEViewPat (GhcPass _1) # 
Instance details

Defined in HsExpr

type XEViewPat (GhcPass _1) = NoExt

type family XELazyPat x Source #

Instances

Instances details
type XELazyPat (GhcPass _1) # 
Instance details

Defined in HsExpr

type XELazyPat (GhcPass _1) = NoExt

type family XWrap x Source #

Instances

Instances details
type XWrap (GhcPass _1) # 
Instance details

Defined in HsExpr

type XWrap (GhcPass _1) = NoExt

type family XXExpr x Source #

Instances

Instances details
type XXExpr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXExpr (GhcPass _1) = NoExt

type ForallXExpr (c :: * -> Constraint) (x :: *) = (c (XVar x), c (XUnboundVar x), c (XConLikeOut x), c (XRecFld x), c (XOverLabel x), c (XIPVar x), c (XOverLitE x), c (XLitE x), c (XLam x), c (XLamCase x), c (XApp x), c (XAppTypeE x), c (XOpApp x), c (XNegApp x), c (XPar x), c (XSectionL x), c (XSectionR x), c (XExplicitTuple x), c (XExplicitSum x), c (XCase x), c (XIf x), c (XMultiIf x), c (XLet x), c (XDo x), c (XExplicitList x), c (XRecordCon x), c (XRecordUpd x), c (XExprWithTySig x), c (XArithSeq x), c (XSCC x), c (XCoreAnn x), c (XBracket x), c (XRnBracketOut x), c (XTcBracketOut x), c (XSpliceE x), c (XProc x), c (XStatic x), c (XArrApp x), c (XArrForm x), c (XTick x), c (XBinTick x), c (XTickPragma x), c (XEWildPat x), c (XEAsPat x), c (XEViewPat x), c (XELazyPat x), c (XWrap x), c (XXExpr x)) Source #

type family XUnambiguous x Source #

Instances

Instances details
type XUnambiguous GhcTc # 
Instance details

Defined in HsTypes

type XUnambiguous GhcRn # 
Instance details

Defined in HsTypes

type XUnambiguous GhcPs # 
Instance details

Defined in HsTypes

type family XAmbiguous x Source #

Instances

Instances details
type XAmbiguous GhcTc # 
Instance details

Defined in HsTypes

type XAmbiguous GhcRn # 
Instance details

Defined in HsTypes

type XAmbiguous GhcPs # 
Instance details

Defined in HsTypes

type family XXAmbiguousFieldOcc x Source #

Instances

Instances details
type XXAmbiguousFieldOcc (GhcPass _1) # 
Instance details

Defined in HsTypes

type ForallXAmbiguousFieldOcc (c :: * -> Constraint) (x :: *) = (c (XUnambiguous x), c (XAmbiguous x), c (XXAmbiguousFieldOcc x)) Source #

type family XPresent x Source #

Instances

Instances details
type XPresent (GhcPass _1) # 
Instance details

Defined in HsExpr

type XPresent (GhcPass _1) = NoExt

type family XMissing x Source #

Instances

Instances details
type XMissing GhcTc # 
Instance details

Defined in HsExpr

type XMissing GhcRn # 
Instance details

Defined in HsExpr

type XMissing GhcPs # 
Instance details

Defined in HsExpr

type family XXTupArg x Source #

Instances

Instances details
type XXTupArg (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXTupArg (GhcPass _1) = NoExt

type ForallXTupArg (c :: * -> Constraint) (x :: *) = (c (XPresent x), c (XMissing x), c (XXTupArg x)) Source #

type family XTypedSplice x Source #

Instances

Instances details
type XTypedSplice (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XUntypedSplice x Source #

Instances

Instances details
type XUntypedSplice (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XQuasiQuote x Source #

Instances

Instances details
type XQuasiQuote (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XSpliced x Source #

Instances

Instances details
type XSpliced (GhcPass _1) # 
Instance details

Defined in HsExpr

type XSpliced (GhcPass _1) = NoExt

type family XXSplice x Source #

Instances

Instances details
type XXSplice (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXSplice (GhcPass _1) = NoExt

type ForallXSplice (c :: * -> Constraint) (x :: *) = (c (XTypedSplice x), c (XUntypedSplice x), c (XQuasiQuote x), c (XSpliced x), c (XXSplice x)) Source #

type family XExpBr x Source #

Instances

Instances details
type XExpBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XExpBr (GhcPass _1) = NoExt

type family XPatBr x Source #

Instances

Instances details
type XPatBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XPatBr (GhcPass _1) = NoExt

type family XDecBrL x Source #

Instances

Instances details
type XDecBrL (GhcPass _1) # 
Instance details

Defined in HsExpr

type XDecBrL (GhcPass _1) = NoExt

type family XDecBrG x Source #

Instances

Instances details
type XDecBrG (GhcPass _1) # 
Instance details

Defined in HsExpr

type XDecBrG (GhcPass _1) = NoExt

type family XTypBr x Source #

Instances

Instances details
type XTypBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XTypBr (GhcPass _1) = NoExt

type family XVarBr x Source #

Instances

Instances details
type XVarBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XVarBr (GhcPass _1) = NoExt

type family XTExpBr x Source #

Instances

Instances details
type XTExpBr (GhcPass _1) # 
Instance details

Defined in HsExpr

type XTExpBr (GhcPass _1) = NoExt

type family XXBracket x Source #

Instances

Instances details
type XXBracket (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXBracket (GhcPass _1) = NoExt

type ForallXBracket (c :: * -> Constraint) (x :: *) = (c (XExpBr x), c (XPatBr x), c (XDecBrL x), c (XDecBrG x), c (XTypBr x), c (XVarBr x), c (XTExpBr x), c (XXBracket x)) Source #

type family XCmdTop x Source #

Instances

Instances details
type XCmdTop GhcTc # 
Instance details

Defined in HsExpr

type XCmdTop GhcRn # 
Instance details

Defined in HsExpr

type XCmdTop GhcPs # 
Instance details

Defined in HsExpr

type family XXCmdTop x Source #

Instances

Instances details
type XXCmdTop (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXCmdTop (GhcPass _1) = NoExt

type ForallXCmdTop (c :: * -> Constraint) (x :: *) = (c (XCmdTop x), c (XXCmdTop x)) Source #

type family XMG x b Source #

Instances

Instances details
type XMG GhcTc b # 
Instance details

Defined in HsExpr

type XMG GhcRn b # 
Instance details

Defined in HsExpr

type XMG GhcRn b = NoExt
type XMG GhcPs b # 
Instance details

Defined in HsExpr

type XMG GhcPs b = NoExt

type family XXMatchGroup x b Source #

Instances

Instances details
type XXMatchGroup (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XXMatchGroup (GhcPass _1) b = NoExt

type ForallXMatchGroup (c :: * -> Constraint) (x :: *) (b :: *) = (c (XMG x b), c (XXMatchGroup x b)) Source #

type family XCMatch x b Source #

Instances

Instances details
type XCMatch (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XCMatch (GhcPass _1) b = NoExt

type family XXMatch x b Source #

Instances

Instances details
type XXMatch (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XXMatch (GhcPass _1) b = NoExt

type ForallXMatch (c :: * -> Constraint) (x :: *) (b :: *) = (c (XCMatch x b), c (XXMatch x b)) Source #

type family XCGRHSs x b Source #

Instances

Instances details
type XCGRHSs (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XCGRHSs (GhcPass _1) b = NoExt

type family XXGRHSs x b Source #

Instances

Instances details
type XXGRHSs (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XXGRHSs (GhcPass _1) b = NoExt

type ForallXGRHSs (c :: * -> Constraint) (x :: *) (b :: *) = (c (XCGRHSs x b), c (XXGRHSs x b)) Source #

type family XCGRHS x b Source #

Instances

Instances details
type XCGRHS (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XCGRHS (GhcPass _1) b = NoExt

type family XXGRHS x b Source #

Instances

Instances details
type XXGRHS (GhcPass _1) b # 
Instance details

Defined in HsExpr

type XXGRHS (GhcPass _1) b = NoExt

type ForallXGRHS (c :: * -> Constraint) (x :: *) (b :: *) = (c (XCGRHS x b), c (XXGRHS x b)) Source #

type family XLastStmt x x' b Source #

Instances

Instances details
type XLastStmt (GhcPass _1) (GhcPass _2) b # 
Instance details

Defined in HsExpr

type XLastStmt (GhcPass _1) (GhcPass _2) b = NoExt

type family XBindStmt x x' b Source #

Instances

Instances details
type XBindStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XBindStmt (GhcPass _1) GhcTc b = Type
type XBindStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XBindStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type family XApplicativeStmt x x' b Source #

Instances

Instances details
type XApplicativeStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XApplicativeStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XApplicativeStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type family XBodyStmt x x' b Source #

Instances

Instances details
type XBodyStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XBodyStmt (GhcPass _1) GhcTc b = Type
type XBodyStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XBodyStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type family XLetStmt x x' b Source #

Instances

Instances details
type XLetStmt (GhcPass _1) (GhcPass _2) b # 
Instance details

Defined in HsExpr

type XLetStmt (GhcPass _1) (GhcPass _2) b = NoExt

type family XParStmt x x' b Source #

Instances

Instances details
type XParStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XParStmt (GhcPass _1) GhcTc b = Type
type XParStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XParStmt (GhcPass _1) GhcRn b = NoExt
type XParStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type XParStmt (GhcPass _1) GhcPs b = NoExt

type family XTransStmt x x' b Source #

Instances

Instances details
type XTransStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type XTransStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XTransStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type family XRecStmt x x' b Source #

Instances

Instances details
type XRecStmt (GhcPass _1) GhcRn b # 
Instance details

Defined in HsExpr

type XRecStmt (GhcPass _1) GhcRn b = NoExt
type XRecStmt (GhcPass _1) GhcPs b # 
Instance details

Defined in HsExpr

type XRecStmt (GhcPass _1) GhcPs b = NoExt
type XRecStmt (GhcPass _1) GhcTc b # 
Instance details

Defined in HsExpr

type family XXStmtLR x x' b Source #

Instances

Instances details
type XXStmtLR (GhcPass _1) (GhcPass _2) b # 
Instance details

Defined in HsExpr

type XXStmtLR (GhcPass _1) (GhcPass _2) b = NoExt

type ForallXStmtLR (c :: * -> Constraint) (x :: *) (x' :: *) (b :: *) = (c (XLastStmt x x' b), c (XBindStmt x x' b), c (XApplicativeStmt x x' b), c (XBodyStmt x x' b), c (XLetStmt x x' b), c (XParStmt x x' b), c (XTransStmt x x' b), c (XRecStmt x x' b), c (XXStmtLR x x' b)) Source #

type family XCmdArrApp x Source #

Instances

Instances details
type XCmdArrApp GhcTc # 
Instance details

Defined in HsExpr

type XCmdArrApp GhcRn # 
Instance details

Defined in HsExpr

type XCmdArrApp GhcPs # 
Instance details

Defined in HsExpr

type family XCmdArrForm x Source #

Instances

Instances details
type XCmdArrForm (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XCmdApp x Source #

Instances

Instances details
type XCmdApp (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdApp (GhcPass _1) = NoExt

type family XCmdLam x Source #

Instances

Instances details
type XCmdLam (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdLam (GhcPass _1) = NoExt

type family XCmdPar x Source #

Instances

Instances details
type XCmdPar (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdPar (GhcPass _1) = NoExt

type family XCmdCase x Source #

Instances

Instances details
type XCmdCase (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdCase (GhcPass _1) = NoExt

type family XCmdIf x Source #

Instances

Instances details
type XCmdIf (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdIf (GhcPass _1) = NoExt

type family XCmdLet x Source #

Instances

Instances details
type XCmdLet (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdLet (GhcPass _1) = NoExt

type family XCmdDo x Source #

Instances

Instances details
type XCmdDo GhcTc # 
Instance details

Defined in HsExpr

type XCmdDo GhcRn # 
Instance details

Defined in HsExpr

type XCmdDo GhcPs # 
Instance details

Defined in HsExpr

type family XCmdWrap x Source #

Instances

Instances details
type XCmdWrap (GhcPass _1) # 
Instance details

Defined in HsExpr

type XCmdWrap (GhcPass _1) = NoExt

type family XXCmd x Source #

Instances

Instances details
type XXCmd (GhcPass _1) # 
Instance details

Defined in HsExpr

type XXCmd (GhcPass _1) = NoExt

type ForallXCmd (c :: * -> Constraint) (x :: *) = (c (XCmdArrApp x), c (XCmdArrForm x), c (XCmdApp x), c (XCmdLam x), c (XCmdPar x), c (XCmdCase x), c (XCmdIf x), c (XCmdLet x), c (XCmdDo x), c (XCmdWrap x), c (XXCmd x)) Source #

type family XParStmtBlock x x' Source #

Instances

Instances details
type XParStmtBlock (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsExpr

type family XXParStmtBlock x x' Source #

Instances

Instances details
type XXParStmtBlock (GhcPass pL) (GhcPass pR) # 
Instance details

Defined in HsExpr

type ForallXParStmtBlock (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XParStmtBlock x x'), c (XXParStmtBlock x x')) Source #

type family XApplicativeArgOne x Source #

Instances

Instances details
type XApplicativeArgOne (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XApplicativeArgMany x Source #

Instances

Instances details
type XApplicativeArgMany (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XXApplicativeArg x Source #

Instances

Instances details
type XXApplicativeArg (GhcPass _1) # 
Instance details

Defined in HsExpr

type family XHsChar x Source #

Instances

Instances details
type XHsChar (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsCharPrim x Source #

Instances

Instances details
type XHsCharPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsString x Source #

Instances

Instances details
type XHsString (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsStringPrim x Source #

Instances

Instances details
type XHsStringPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsInt x Source #

Instances

Instances details
type XHsInt (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsInt (GhcPass _1) = NoExt

type family XHsIntPrim x Source #

Instances

Instances details
type XHsIntPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsWordPrim x Source #

Instances

Instances details
type XHsWordPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsInt64Prim x Source #

Instances

Instances details
type XHsInt64Prim (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsWord64Prim x Source #

Instances

Instances details
type XHsWord64Prim (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsInteger x Source #

Instances

Instances details
type XHsInteger (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsRat x Source #

Instances

Instances details
type XHsRat (GhcPass _1) # 
Instance details

Defined in HsLit

type XHsRat (GhcPass _1) = NoExt

type family XHsFloatPrim x Source #

Instances

Instances details
type XHsFloatPrim (GhcPass _1) # 
Instance details

Defined in HsLit

type family XHsDoublePrim x Source #

Instances

Instances details
type XHsDoublePrim (GhcPass _1) # 
Instance details

Defined in HsLit

type family XXLit x Source #

Instances

Instances details
type XXLit (GhcPass _1) # 
Instance details

Defined in HsLit

type XXLit (GhcPass _1) = NoExt

type ForallXHsLit (c :: * -> Constraint) (x :: *) = (c (XHsChar x), c (XHsCharPrim x), c (XHsDoublePrim x), c (XHsFloatPrim x), c (XHsInt x), c (XHsInt64Prim x), c (XHsIntPrim x), c (XHsInteger x), c (XHsRat x), c (XHsString x), c (XHsStringPrim x), c (XHsWord64Prim x), c (XHsWordPrim x), c (XXLit x)) Source #

Helper to apply a constraint to all extension points. It has one entry per extension point type family.

type family XOverLit x Source #

Instances

Instances details
type XOverLit GhcTc # 
Instance details

Defined in HsLit

type XOverLit GhcRn # 
Instance details

Defined in HsLit

type XOverLit GhcPs # 
Instance details

Defined in HsLit

type family XXOverLit x Source #

Instances

Instances details
type XXOverLit (GhcPass _1) # 
Instance details

Defined in HsLit

type XXOverLit (GhcPass _1) = NoExt

type ForallXOverLit (c :: * -> Constraint) (x :: *) = (c (XOverLit x), c (XXOverLit x)) Source #

type family XWildPat x Source #

Instances

Instances details
type XWildPat GhcTc # 
Instance details

Defined in HsPat

type XWildPat GhcRn # 
Instance details

Defined in HsPat

type XWildPat GhcPs # 
Instance details

Defined in HsPat

type family XVarPat x Source #

Instances

Instances details
type XVarPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XVarPat (GhcPass _1) = NoExt

type family XLazyPat x Source #

Instances

Instances details
type XLazyPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XLazyPat (GhcPass _1) = NoExt

type family XAsPat x Source #

Instances

Instances details
type XAsPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XAsPat (GhcPass _1) = NoExt

type family XParPat x Source #

Instances

Instances details
type XParPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XParPat (GhcPass _1) = NoExt

type family XBangPat x Source #

Instances

Instances details
type XBangPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XBangPat (GhcPass _1) = NoExt

type family XListPat x Source #

Instances

Instances details
type XListPat GhcTc # 
Instance details

Defined in HsPat

type XListPat GhcRn # 
Instance details

Defined in HsPat

type XListPat GhcPs # 
Instance details

Defined in HsPat

type family XTuplePat x Source #

Instances

Instances details
type XTuplePat GhcTc # 
Instance details

Defined in HsPat

type XTuplePat GhcRn # 
Instance details

Defined in HsPat

type XTuplePat GhcPs # 
Instance details

Defined in HsPat

type family XSumPat x Source #

Instances

Instances details
type XSumPat GhcTc # 
Instance details

Defined in HsPat

type XSumPat GhcTc = [Type]
type XSumPat GhcRn # 
Instance details

Defined in HsPat

type XSumPat GhcPs # 
Instance details

Defined in HsPat

type family XConPat x Source #

type family XViewPat x Source #

Instances

Instances details
type XViewPat GhcTc # 
Instance details

Defined in HsPat

type XViewPat GhcRn # 
Instance details

Defined in HsPat

type XViewPat GhcPs # 
Instance details

Defined in HsPat

type family XSplicePat x Source #

Instances

Instances details
type XSplicePat (GhcPass _1) # 
Instance details

Defined in HsPat

type family XLitPat x Source #

Instances

Instances details
type XLitPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XLitPat (GhcPass _1) = NoExt

type family XNPat x Source #

Instances

Instances details
type XNPat GhcTc # 
Instance details

Defined in HsPat

type XNPat GhcRn # 
Instance details

Defined in HsPat

type XNPat GhcPs # 
Instance details

Defined in HsPat

type family XNPlusKPat x Source #

Instances

Instances details
type XNPlusKPat GhcTc # 
Instance details

Defined in HsPat

type XNPlusKPat GhcRn # 
Instance details

Defined in HsPat

type XNPlusKPat GhcPs # 
Instance details

Defined in HsPat

type family XSigPat x Source #

Instances

Instances details
type XSigPat GhcTc # 
Instance details

Defined in HsPat

type XSigPat GhcRn # 
Instance details

Defined in HsPat

type XSigPat GhcPs # 
Instance details

Defined in HsPat

type family XCoPat x Source #

Instances

Instances details
type XCoPat (GhcPass _1) # 
Instance details

Defined in HsPat

type XCoPat (GhcPass _1) = NoExt

type family XXPat x Source #

Instances

Instances details
type XXPat (GhcPass p) # 
Instance details

Defined in HsPat

type XXPat (GhcPass p) = Located (Pat (GhcPass p))

type ForallXPat (c :: * -> Constraint) (x :: *) = (c (XWildPat x), c (XVarPat x), c (XLazyPat x), c (XAsPat x), c (XParPat x), c (XBangPat x), c (XListPat x), c (XTuplePat x), c (XSumPat x), c (XViewPat x), c (XSplicePat x), c (XLitPat x), c (XNPat x), c (XNPlusKPat x), c (XSigPat x), c (XCoPat x), c (XXPat x)) Source #

type family XHsQTvs x Source #

Instances

Instances details
type XHsQTvs GhcTc # 
Instance details

Defined in HsTypes

type XHsQTvs GhcRn # 
Instance details

Defined in HsTypes

type XHsQTvs GhcPs # 
Instance details

Defined in HsTypes

type family XXLHsQTyVars x Source #

Instances

Instances details
type XXLHsQTyVars (GhcPass _1) # 
Instance details

Defined in HsTypes

type ForallXLHsQTyVars (c :: * -> Constraint) (x :: *) = (c (XHsQTvs x), c (XXLHsQTyVars x)) Source #

type family XHsIB x b Source #

Instances

Instances details
type XHsIB GhcTc _1 # 
Instance details

Defined in HsTypes

type XHsIB GhcTc _1 = [Name]
type XHsIB GhcRn _1 # 
Instance details

Defined in HsTypes

type XHsIB GhcRn _1 = [Name]
type XHsIB GhcPs _1 # 
Instance details

Defined in HsTypes

type XHsIB GhcPs _1 = NoExt

type family XXHsImplicitBndrs x b Source #

Instances

Instances details
type XXHsImplicitBndrs (GhcPass _1) _2 # 
Instance details

Defined in HsTypes

type ForallXHsImplicitBndrs (c :: * -> Constraint) (x :: *) (b :: *) = (c (XHsIB x b), c (XXHsImplicitBndrs x b)) Source #

type family XHsWC x b Source #

Instances

Instances details
type XHsWC GhcTc b # 
Instance details

Defined in HsTypes

type XHsWC GhcTc b = [Name]
type XHsWC GhcRn b # 
Instance details

Defined in HsTypes

type XHsWC GhcRn b = [Name]
type XHsWC GhcPs b # 
Instance details

Defined in HsTypes

type XHsWC GhcPs b = NoExt

type family XXHsWildCardBndrs x b Source #

Instances

Instances details
type XXHsWildCardBndrs (GhcPass _1) b # 
Instance details

Defined in HsTypes

type ForallXHsWildCardBndrs (c :: * -> Constraint) (x :: *) (b :: *) = (c (XHsWC x b), c (XXHsWildCardBndrs x b)) Source #

type family XForAllTy x Source #

Instances

Instances details
type XForAllTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XForAllTy (GhcPass _1) = NoExt

type family XQualTy x Source #

Instances

Instances details
type XQualTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XQualTy (GhcPass _1) = NoExt

type family XTyVar x Source #

Instances

Instances details
type XTyVar (GhcPass _1) # 
Instance details

Defined in HsTypes

type XTyVar (GhcPass _1) = NoExt

type family XAppTy x Source #

Instances

Instances details
type XAppTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XAppTy (GhcPass _1) = NoExt

type family XAppKindTy x Source #

Instances

Instances details
type XAppKindTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type family XFunTy x Source #

Instances

Instances details
type XFunTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XFunTy (GhcPass _1) = NoExt

type family XListTy x Source #

Instances

Instances details
type XListTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XListTy (GhcPass _1) = NoExt

type family XTupleTy x Source #

Instances

Instances details
type XTupleTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XTupleTy (GhcPass _1) = NoExt

type family XSumTy x Source #

Instances

Instances details
type XSumTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XSumTy (GhcPass _1) = NoExt

type family XOpTy x Source #

Instances

Instances details
type XOpTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XOpTy (GhcPass _1) = NoExt

type family XParTy x Source #

Instances

Instances details
type XParTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XParTy (GhcPass _1) = NoExt

type family XIParamTy x Source #

Instances

Instances details
type XIParamTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XIParamTy (GhcPass _1) = NoExt

type family XStarTy x Source #

Instances

Instances details
type XStarTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XStarTy (GhcPass _1) = NoExt

type family XKindSig x Source #

Instances

Instances details
type XKindSig (GhcPass _1) # 
Instance details

Defined in HsTypes

type XKindSig (GhcPass _1) = NoExt

type family XSpliceTy x Source #

Instances

Instances details
type XSpliceTy GhcTc # 
Instance details

Defined in HsTypes

type XSpliceTy GhcRn # 
Instance details

Defined in HsTypes

type XSpliceTy GhcPs # 
Instance details

Defined in HsTypes

type family XDocTy x Source #

Instances

Instances details
type XDocTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XDocTy (GhcPass _1) = NoExt

type family XBangTy x Source #

Instances

Instances details
type XBangTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XBangTy (GhcPass _1) = NoExt

type family XRecTy x Source #

Instances

Instances details
type XRecTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type XRecTy (GhcPass _1) = NoExt

type family XExplicitListTy x Source #

Instances

Instances details
type XExplicitListTy GhcTc # 
Instance details

Defined in HsTypes

type XExplicitListTy GhcRn # 
Instance details

Defined in HsTypes

type XExplicitListTy GhcPs # 
Instance details

Defined in HsTypes

type family XExplicitTupleTy x Source #

Instances

Instances details
type XExplicitTupleTy GhcTc # 
Instance details

Defined in HsTypes

type XExplicitTupleTy GhcRn # 
Instance details

Defined in HsTypes

type XExplicitTupleTy GhcPs # 
Instance details

Defined in HsTypes

type family XTyLit x Source #

Instances

Instances details
type XTyLit (GhcPass _1) # 
Instance details

Defined in HsTypes

type XTyLit (GhcPass _1) = NoExt

type family XWildCardTy x Source #

Instances

Instances details
type XWildCardTy (GhcPass _1) # 
Instance details

Defined in HsTypes

type family XXType x Source #

Instances

Instances details
type XXType (GhcPass _1) # 
Instance details

Defined in HsTypes

type ForallXType (c :: * -> Constraint) (x :: *) = (c (XForAllTy x), c (XQualTy x), c (XTyVar x), c (XAppTy x), c (XAppKindTy x), c (XFunTy x), c (XListTy x), c (XTupleTy x), c (XSumTy x), c (XOpTy x), c (XParTy x), c (XIParamTy x), c (XStarTy x), c (XKindSig x), c (XSpliceTy x), c (XDocTy x), c (XBangTy x), c (XRecTy x), c (XExplicitListTy x), c (XExplicitTupleTy x), c (XTyLit x), c (XWildCardTy x), c (XXType x)) Source #

Helper to apply a constraint to all extension points. It has one entry per extension point type family.

type family XUserTyVar x Source #

Instances

Instances details
type XUserTyVar (GhcPass _1) # 
Instance details

Defined in HsTypes

type family XKindedTyVar x Source #

Instances

Instances details
type XKindedTyVar (GhcPass _1) # 
Instance details

Defined in HsTypes

type family XXTyVarBndr x Source #

Instances

Instances details
type XXTyVarBndr (GhcPass _1) # 
Instance details

Defined in HsTypes

type ForallXTyVarBndr (c :: * -> Constraint) (x :: *) = (c (XUserTyVar x), c (XKindedTyVar x), c (XXTyVarBndr x)) Source #

type family XConDeclField x Source #

Instances

Instances details
type XConDeclField (GhcPass _1) # 
Instance details

Defined in HsTypes

type family XXConDeclField x Source #

Instances

Instances details
type XXConDeclField (GhcPass _1) # 
Instance details

Defined in HsTypes

type ForallXConDeclField (c :: * -> Constraint) (x :: *) = (c (XConDeclField x), c (XXConDeclField x)) Source #

type family XCFieldOcc x Source #

Instances

Instances details
type XCFieldOcc GhcTc # 
Instance details

Defined in HsTypes

type XCFieldOcc GhcRn # 
Instance details

Defined in HsTypes

type XCFieldOcc GhcPs # 
Instance details

Defined in HsTypes

type family XXFieldOcc x Source #

Instances

Instances details
type XXFieldOcc (GhcPass _1) # 
Instance details

Defined in HsTypes

type ForallXFieldOcc (c :: * -> Constraint) (x :: *) = (c (XCFieldOcc x), c (XXFieldOcc x)) Source #

type family XCImportDecl x Source #

Instances

Instances details
type XCImportDecl (GhcPass _1) # 
Instance details

Defined in HsImpExp

type family XXImportDecl x Source #

Instances

Instances details
type XXImportDecl (GhcPass _1) # 
Instance details

Defined in HsImpExp

type ForallXImportDecl (c :: * -> Constraint) (x :: *) = (c (XCImportDecl x), c (XXImportDecl x)) Source #

type family XIEVar x Source #

Instances

Instances details
type XIEVar (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEVar (GhcPass _1) = NoExt

type family XIEThingAbs x Source #

Instances

Instances details
type XIEThingAbs (GhcPass _1) # 
Instance details

Defined in HsImpExp

type family XIEThingAll x Source #

Instances

Instances details
type XIEThingAll (GhcPass _1) # 
Instance details

Defined in HsImpExp

type family XIEThingWith x Source #

Instances

Instances details
type XIEThingWith (GhcPass _1) # 
Instance details

Defined in HsImpExp

type family XIEModuleContents x Source #

Instances

Instances details
type XIEModuleContents (GhcPass _1) # 
Instance details

Defined in HsImpExp

type family XIEGroup x Source #

Instances

Instances details
type XIEGroup (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEGroup (GhcPass _1) = NoExt

type family XIEDoc x Source #

Instances

Instances details
type XIEDoc (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XIEDoc (GhcPass _1) = NoExt

type family XIEDocNamed x Source #

Instances

Instances details
type XIEDocNamed (GhcPass _1) # 
Instance details

Defined in HsImpExp

type family XXIE x Source #

Instances

Instances details
type XXIE (GhcPass _1) # 
Instance details

Defined in HsImpExp

type XXIE (GhcPass _1) = NoExt

type ForallXIE (c :: * -> Constraint) (x :: *) = (c (XIEVar x), c (XIEThingAbs x), c (XIEThingAll x), c (XIEThingWith x), c (XIEModuleContents x), c (XIEGroup x), c (XIEDoc x), c (XIEDocNamed x), c (XXIE x)) Source #

class Convertable a b | a -> b where Source #

Conversion of annotations from one type index to another. This is required where the AST is converted from one pass to another, and the extension values need to be brought along if possible. So for example a SourceText is converted via id, but needs a type signature to keep the type checker happy.

Methods

convert :: a -> b Source #

Instances

Instances details
Convertable a a # 
Instance details

Defined in HsExtension

Methods

convert :: a -> a Source #

type ConvertIdX a b = (XHsDoublePrim a ~ XHsDoublePrim b, XHsFloatPrim a ~ XHsFloatPrim b, XHsRat a ~ XHsRat b, XHsInteger a ~ XHsInteger b, XHsWord64Prim a ~ XHsWord64Prim b, XHsInt64Prim a ~ XHsInt64Prim b, XHsWordPrim a ~ XHsWordPrim b, XHsIntPrim a ~ XHsIntPrim b, XHsInt a ~ XHsInt b, XHsStringPrim a ~ XHsStringPrim b, XHsString a ~ XHsString b, XHsCharPrim a ~ XHsCharPrim b, XHsChar a ~ XHsChar b, XXLit a ~ XXLit b) Source #

A constraint capturing all the extension points that can be converted via instance Convertable a a

type OutputableX p = (Outputable (XIPBinds p), Outputable (XViaStrategy p), Outputable (XViaStrategy GhcRn)) Source #

Provide a summary constraint that gives all am Outputable constraint to extension points needing one

type OutputableBndrId id = (OutputableBndr (NameOrRdrName (IdP id)), OutputableBndr (IdP id), OutputableBndr (NameOrRdrName (IdP (NoGhcTc id))), OutputableBndr (IdP (NoGhcTc id)), NoGhcTc id ~ NoGhcTc (NoGhcTc id), OutputableX id, OutputableX (NoGhcTc id)) Source #

Constraint type to bundle up the requirement for OutputableBndr on both the id and the NameOrRdrName type for it