Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type IsSrcSpanAnn p a = (Anno (IdGhcP p) ~ SrcSpanAnn' (EpAnn a), IsPass p)
- data GhcPass (c :: Pass) where
- data Pass
- = Parsed
- | Renamed
- | Typechecked
- type GhcPs = GhcPass 'Parsed
- type GhcRn = GhcPass 'Renamed
- type GhcTc = GhcPass 'Typechecked
- class (NoGhcTcPass (NoGhcTcPass p) ~ NoGhcTcPass p, IsPass (NoGhcTcPass p)) => IsPass p where
- type family IdGhcP pass where ...
- type family NoGhcTcPass (p :: Pass) :: Pass where ...
- type OutputableBndrId pass = (OutputableBndr (IdGhcP pass), OutputableBndr (IdGhcP (NoGhcTcPass pass)), Outputable (GenLocated (Anno (IdGhcP pass)) (IdGhcP pass)), Outputable (GenLocated (Anno (IdGhcP (NoGhcTcPass pass))) (IdGhcP (NoGhcTcPass pass))), IsPass pass)
- pprIfPs :: forall p. IsPass p => (p ~ 'Parsed => SDoc) -> SDoc
- pprIfRn :: forall p. IsPass p => (p ~ 'Renamed => SDoc) -> SDoc
- pprIfTc :: forall p. IsPass p => (p ~ 'Typechecked => SDoc) -> SDoc
Documentation
type IsSrcSpanAnn p a = (Anno (IdGhcP p) ~ SrcSpanAnn' (EpAnn a), IsPass p) Source #
data GhcPass (c :: Pass) where Source #
Used as a data type index for the hsSyn AST; also serves as a singleton type for Pass
Instances
Eq (IE GhcTc) Source # | |
Eq (IE GhcRn) Source # | |
Eq (IE GhcPs) Source # | |
Data (HsSplice GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcTc -> c (HsSplice GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcTc) # toConstr :: HsSplice GhcTc -> Constr # dataTypeOf :: HsSplice GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcTc -> HsSplice GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) # | |
Data (HsSplice GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcRn -> c (HsSplice GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcRn) # toConstr :: HsSplice GhcRn -> Constr # dataTypeOf :: HsSplice GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcRn -> HsSplice GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) # | |
Data (HsSplice GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcPs -> c (HsSplice GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcPs) # toConstr :: HsSplice GhcPs -> Constr # dataTypeOf :: HsSplice GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcPs -> HsSplice GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) # | |
Data (HsExpr GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcTc -> c (HsExpr GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcTc) # toConstr :: HsExpr GhcTc -> Constr # dataTypeOf :: HsExpr GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcTc -> HsExpr GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) # | |
Data (HsExpr GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcRn -> c (HsExpr GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcRn) # toConstr :: HsExpr GhcRn -> Constr # dataTypeOf :: HsExpr GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcRn -> HsExpr GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) # | |
Data (HsExpr GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcPs -> c (HsExpr GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcPs) # toConstr :: HsExpr GhcPs -> Constr # dataTypeOf :: HsExpr GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcPs -> HsExpr GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) # | |
Typeable p => Data (GhcPass p) Source # | |
Defined in GHC.Hs.Extension gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GhcPass p -> c (GhcPass p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GhcPass p) # toConstr :: GhcPass p -> Constr # dataTypeOf :: GhcPass p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GhcPass p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GhcPass p)) # gmapT :: (forall b. Data b => b -> b) -> GhcPass p -> GhcPass p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GhcPass p -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GhcPass p -> r # gmapQ :: (forall d. Data d => d -> u) -> GhcPass p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GhcPass p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GhcPass p -> m (GhcPass p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GhcPass p -> m (GhcPass p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GhcPass p -> m (GhcPass p) # | |
Data (IE GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcTc -> c (IE GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcTc) # toConstr :: IE GhcTc -> Constr # dataTypeOf :: IE GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> IE GhcTc -> IE GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> IE GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) # | |
Data (IE GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcRn -> c (IE GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcRn) # toConstr :: IE GhcRn -> Constr # dataTypeOf :: IE GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> IE GhcRn -> IE GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> IE GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) # | |
Data (IE GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcPs -> c (IE GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcPs) # toConstr :: IE GhcPs -> Constr # dataTypeOf :: IE GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> IE GhcPs -> IE GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> IE GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) # | |
Data (ImportDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcTc -> c (ImportDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcTc) # toConstr :: ImportDecl GhcTc -> Constr # dataTypeOf :: ImportDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcTc -> ImportDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) # | |
Data (ImportDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcRn -> c (ImportDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcRn) # toConstr :: ImportDecl GhcRn -> Constr # dataTypeOf :: ImportDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcRn -> ImportDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) # | |
Data (ImportDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcPs -> c (ImportDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcPs) # toConstr :: ImportDecl GhcPs -> Constr # dataTypeOf :: ImportDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcPs -> ImportDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) # | |
Data (HsOverLit GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcTc -> c (HsOverLit GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcTc) # toConstr :: HsOverLit GhcTc -> Constr # dataTypeOf :: HsOverLit GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcTc -> HsOverLit GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) # | |
Data (HsOverLit GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcRn -> c (HsOverLit GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcRn) # toConstr :: HsOverLit GhcRn -> Constr # dataTypeOf :: HsOverLit GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcRn -> HsOverLit GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) # | |
Data (HsOverLit GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcPs -> c (HsOverLit GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcPs) # toConstr :: HsOverLit GhcPs -> Constr # dataTypeOf :: HsOverLit GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcPs -> HsOverLit GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) # | |
Data (HsLit GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcTc -> c (HsLit GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcTc) # toConstr :: HsLit GhcTc -> Constr # dataTypeOf :: HsLit GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsLit GhcTc -> HsLit GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) # | |
Data (HsLit GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcRn -> c (HsLit GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcRn) # toConstr :: HsLit GhcRn -> Constr # dataTypeOf :: HsLit GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsLit GhcRn -> HsLit GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) # | |
Data (HsLit GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcPs -> c (HsLit GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcPs) # toConstr :: HsLit GhcPs -> Constr # dataTypeOf :: HsLit GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsLit GhcPs -> HsLit GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) # | |
Data (Pat GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcTc -> c (Pat GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcTc) # toConstr :: Pat GhcTc -> Constr # dataTypeOf :: Pat GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> Pat GhcTc -> Pat GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) # | |
Data (Pat GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcRn -> c (Pat GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcRn) # toConstr :: Pat GhcRn -> Constr # dataTypeOf :: Pat GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> Pat GhcRn -> Pat GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) # | |
Data (Pat GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcPs -> c (Pat GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcPs) # toConstr :: Pat GhcPs -> Constr # dataTypeOf :: Pat GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> Pat GhcPs -> Pat GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) # | |
Data (AmbiguousFieldOcc GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcTc -> c (AmbiguousFieldOcc GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcTc) # toConstr :: AmbiguousFieldOcc GhcTc -> Constr # dataTypeOf :: AmbiguousFieldOcc GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcTc -> AmbiguousFieldOcc GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) # | |
Data (AmbiguousFieldOcc GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcRn -> c (AmbiguousFieldOcc GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcRn) # toConstr :: AmbiguousFieldOcc GhcRn -> Constr # dataTypeOf :: AmbiguousFieldOcc GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcRn -> AmbiguousFieldOcc GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) # | |
Data (AmbiguousFieldOcc GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcPs -> c (AmbiguousFieldOcc GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcPs) # toConstr :: AmbiguousFieldOcc GhcPs -> Constr # dataTypeOf :: AmbiguousFieldOcc GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcPs -> AmbiguousFieldOcc GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) # | |
Data (FieldOcc GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcTc -> c (FieldOcc GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcTc) # toConstr :: FieldOcc GhcTc -> Constr # dataTypeOf :: FieldOcc GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcTc -> FieldOcc GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) # | |
Data (FieldOcc GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcRn -> c (FieldOcc GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcRn) # toConstr :: FieldOcc GhcRn -> Constr # dataTypeOf :: FieldOcc GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcRn -> FieldOcc GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) # | |
Data (FieldOcc GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcPs -> c (FieldOcc GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcPs) # toConstr :: FieldOcc GhcPs -> Constr # dataTypeOf :: FieldOcc GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcPs -> FieldOcc GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) # | |
Data (ConDeclField GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcTc -> c (ConDeclField GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcTc) # toConstr :: ConDeclField GhcTc -> Constr # dataTypeOf :: ConDeclField GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcTc -> ConDeclField GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) # | |
Data (ConDeclField GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcRn -> c (ConDeclField GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcRn) # toConstr :: ConDeclField GhcRn -> Constr # dataTypeOf :: ConDeclField GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcRn -> ConDeclField GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) # | |
Data (ConDeclField GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcPs -> c (ConDeclField GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcPs) # toConstr :: ConDeclField GhcPs -> Constr # dataTypeOf :: ConDeclField GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcPs -> ConDeclField GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) # | |
Data (HsArrow GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcTc -> c (HsArrow GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcTc) # toConstr :: HsArrow GhcTc -> Constr # dataTypeOf :: HsArrow GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcTc -> HsArrow GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) # | |
Data (HsArrow GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcRn -> c (HsArrow GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcRn) # toConstr :: HsArrow GhcRn -> Constr # dataTypeOf :: HsArrow GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcRn -> HsArrow GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) # | |
Data (HsArrow GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcPs -> c (HsArrow GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcPs) # toConstr :: HsArrow GhcPs -> Constr # dataTypeOf :: HsArrow GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcPs -> HsArrow GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) # | |
Data (HsType GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcTc -> c (HsType GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcTc) # toConstr :: HsType GhcTc -> Constr # dataTypeOf :: HsType GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsType GhcTc -> HsType GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) # | |
Data (HsType GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcRn -> c (HsType GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcRn) # toConstr :: HsType GhcRn -> Constr # dataTypeOf :: HsType GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsType GhcRn -> HsType GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) # | |
Data (HsType GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcPs -> c (HsType GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcPs) # toConstr :: HsType GhcPs -> Constr # dataTypeOf :: HsType GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsType GhcPs -> HsType GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) # | |
Data (HsSigType GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcTc -> c (HsSigType GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcTc) # toConstr :: HsSigType GhcTc -> Constr # dataTypeOf :: HsSigType GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcTc -> HsSigType GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) # | |
Data (HsSigType GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcRn -> c (HsSigType GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcRn) # toConstr :: HsSigType GhcRn -> Constr # dataTypeOf :: HsSigType GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcRn -> HsSigType GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) # | |
Data (HsSigType GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcPs -> c (HsSigType GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcPs) # toConstr :: HsSigType GhcPs -> Constr # dataTypeOf :: HsSigType GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcPs -> HsSigType GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) # | |
Data (HsPatSigType GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcTc -> c (HsPatSigType GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcTc) # toConstr :: HsPatSigType GhcTc -> Constr # dataTypeOf :: HsPatSigType GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcTc -> HsPatSigType GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) # | |
Data (HsPatSigType GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcRn -> c (HsPatSigType GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcRn) # toConstr :: HsPatSigType GhcRn -> Constr # dataTypeOf :: HsPatSigType GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcRn -> HsPatSigType GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) # | |
Data (HsPatSigType GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcPs -> c (HsPatSigType GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcPs) # toConstr :: HsPatSigType GhcPs -> Constr # dataTypeOf :: HsPatSigType GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcPs -> HsPatSigType GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) # | |
Data (LHsQTyVars GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcTc -> c (LHsQTyVars GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcTc) # toConstr :: LHsQTyVars GhcTc -> Constr # dataTypeOf :: LHsQTyVars GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcTc -> LHsQTyVars GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) # | |
Data (LHsQTyVars GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcRn -> c (LHsQTyVars GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcRn) # toConstr :: LHsQTyVars GhcRn -> Constr # dataTypeOf :: LHsQTyVars GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcRn -> LHsQTyVars GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) # | |
Data (LHsQTyVars GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcPs -> c (LHsQTyVars GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcPs) # toConstr :: LHsQTyVars GhcPs -> Constr # dataTypeOf :: LHsQTyVars GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcPs -> LHsQTyVars GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) # | |
Data (HsForAllTelescope GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcTc -> c (HsForAllTelescope GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcTc) # toConstr :: HsForAllTelescope GhcTc -> Constr # dataTypeOf :: HsForAllTelescope GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcTc -> HsForAllTelescope GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) # | |
Data (HsForAllTelescope GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcRn -> c (HsForAllTelescope GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcRn) # toConstr :: HsForAllTelescope GhcRn -> Constr # dataTypeOf :: HsForAllTelescope GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcRn -> HsForAllTelescope GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) # | |
Data (HsForAllTelescope GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcPs -> c (HsForAllTelescope GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcPs) # toConstr :: HsForAllTelescope GhcPs -> Constr # dataTypeOf :: HsForAllTelescope GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcPs -> HsForAllTelescope GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) # | |
Data (HsPatSynDir GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSynDir GhcTc -> c (HsPatSynDir GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcTc) # toConstr :: HsPatSynDir GhcTc -> Constr # dataTypeOf :: HsPatSynDir GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcTc -> HsPatSynDir GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) # | |
Data (HsPatSynDir GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSynDir GhcRn -> c (HsPatSynDir GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcRn) # toConstr :: HsPatSynDir GhcRn -> Constr # dataTypeOf :: HsPatSynDir GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcRn -> HsPatSynDir GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) # | |
Data (HsPatSynDir GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSynDir GhcPs -> c (HsPatSynDir GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcPs) # toConstr :: HsPatSynDir GhcPs -> Constr # dataTypeOf :: HsPatSynDir GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcPs -> HsPatSynDir GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) # | |
Data (RecordPatSynField GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecordPatSynField GhcTc -> c (RecordPatSynField GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RecordPatSynField GhcTc) # toConstr :: RecordPatSynField GhcTc -> Constr # dataTypeOf :: RecordPatSynField GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RecordPatSynField GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RecordPatSynField GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> RecordPatSynField GhcTc -> RecordPatSynField GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> RecordPatSynField GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordPatSynField GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcTc -> m (RecordPatSynField GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcTc -> m (RecordPatSynField GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcTc -> m (RecordPatSynField GhcTc) # | |
Data (RecordPatSynField GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecordPatSynField GhcRn -> c (RecordPatSynField GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RecordPatSynField GhcRn) # toConstr :: RecordPatSynField GhcRn -> Constr # dataTypeOf :: RecordPatSynField GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RecordPatSynField GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RecordPatSynField GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> RecordPatSynField GhcRn -> RecordPatSynField GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> RecordPatSynField GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordPatSynField GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcRn -> m (RecordPatSynField GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcRn -> m (RecordPatSynField GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcRn -> m (RecordPatSynField GhcRn) # | |
Data (RecordPatSynField GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecordPatSynField GhcPs -> c (RecordPatSynField GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RecordPatSynField GhcPs) # toConstr :: RecordPatSynField GhcPs -> Constr # dataTypeOf :: RecordPatSynField GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RecordPatSynField GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RecordPatSynField GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> RecordPatSynField GhcPs -> RecordPatSynField GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> RecordPatSynField GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordPatSynField GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcPs -> m (RecordPatSynField GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcPs -> m (RecordPatSynField GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcPs -> m (RecordPatSynField GhcPs) # | |
Data (FixitySig GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixitySig GhcTc -> c (FixitySig GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcTc) # toConstr :: FixitySig GhcTc -> Constr # dataTypeOf :: FixitySig GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcTc -> FixitySig GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) # | |
Data (FixitySig GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixitySig GhcRn -> c (FixitySig GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcRn) # toConstr :: FixitySig GhcRn -> Constr # dataTypeOf :: FixitySig GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcRn -> FixitySig GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) # | |
Data (FixitySig GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FixitySig GhcPs -> c (FixitySig GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcPs) # toConstr :: FixitySig GhcPs -> Constr # dataTypeOf :: FixitySig GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcPs -> FixitySig GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) # | |
Data (Sig GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sig GhcTc -> c (Sig GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcTc) # toConstr :: Sig GhcTc -> Constr # dataTypeOf :: Sig GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> Sig GhcTc -> Sig GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> Sig GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) # | |
Data (Sig GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sig GhcRn -> c (Sig GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcRn) # toConstr :: Sig GhcRn -> Constr # dataTypeOf :: Sig GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> Sig GhcRn -> Sig GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> Sig GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) # | |
Data (Sig GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sig GhcPs -> c (Sig GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcPs) # toConstr :: Sig GhcPs -> Constr # dataTypeOf :: Sig GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> Sig GhcPs -> Sig GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> Sig GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) # | |
Data (IPBind GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPBind GhcTc -> c (IPBind GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcTc) # toConstr :: IPBind GhcTc -> Constr # dataTypeOf :: IPBind GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> IPBind GhcTc -> IPBind GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) # | |
Data (IPBind GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPBind GhcRn -> c (IPBind GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcRn) # toConstr :: IPBind GhcRn -> Constr # dataTypeOf :: IPBind GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> IPBind GhcRn -> IPBind GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) # | |
Data (IPBind GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IPBind GhcPs -> c (IPBind GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcPs) # toConstr :: IPBind GhcPs -> Constr # dataTypeOf :: IPBind GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> IPBind GhcPs -> IPBind GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) # | |
Data (HsIPBinds GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPBinds GhcTc -> c (HsIPBinds GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcTc) # toConstr :: HsIPBinds GhcTc -> Constr # dataTypeOf :: HsIPBinds GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcTc -> HsIPBinds GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) # | |
Data (HsIPBinds GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPBinds GhcRn -> c (HsIPBinds GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcRn) # toConstr :: HsIPBinds GhcRn -> Constr # dataTypeOf :: HsIPBinds GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcRn -> HsIPBinds GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) # | |
Data (HsIPBinds GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPBinds GhcPs -> c (HsIPBinds GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcPs) # toConstr :: HsIPBinds GhcPs -> Constr # dataTypeOf :: HsIPBinds GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcPs -> HsIPBinds GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) # | |
Data (ABExport GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABExport GhcTc -> c (ABExport GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ABExport GhcTc) # toConstr :: ABExport GhcTc -> Constr # dataTypeOf :: ABExport GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ABExport GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ABExport GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ABExport GhcTc -> ABExport GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ABExport GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ABExport GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ABExport GhcTc -> m (ABExport GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcTc -> m (ABExport GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcTc -> m (ABExport GhcTc) # | |
Data (ABExport GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABExport GhcRn -> c (ABExport GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ABExport GhcRn) # toConstr :: ABExport GhcRn -> Constr # dataTypeOf :: ABExport GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ABExport GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ABExport GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ABExport GhcRn -> ABExport GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ABExport GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ABExport GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ABExport GhcRn -> m (ABExport GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcRn -> m (ABExport GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcRn -> m (ABExport GhcRn) # | |
Data (ABExport GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ABExport GhcPs -> c (ABExport GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ABExport GhcPs) # toConstr :: ABExport GhcPs -> Constr # dataTypeOf :: ABExport GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ABExport GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ABExport GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ABExport GhcPs -> ABExport GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ABExport GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ABExport GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ABExport GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ABExport GhcPs -> m (ABExport GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcPs -> m (ABExport GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ABExport GhcPs -> m (ABExport GhcPs) # | |
Data (RoleAnnotDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcTc -> c (RoleAnnotDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcTc) # toConstr :: RoleAnnotDecl GhcTc -> Constr # dataTypeOf :: RoleAnnotDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcTc -> RoleAnnotDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) # | |
Data (RoleAnnotDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcRn -> c (RoleAnnotDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcRn) # toConstr :: RoleAnnotDecl GhcRn -> Constr # dataTypeOf :: RoleAnnotDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcRn -> RoleAnnotDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) # | |
Data (RoleAnnotDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcPs -> c (RoleAnnotDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcPs) # toConstr :: RoleAnnotDecl GhcPs -> Constr # dataTypeOf :: RoleAnnotDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcPs -> RoleAnnotDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) # | |
Data (AnnProvenance GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnProvenance GhcTc -> c (AnnProvenance GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnProvenance GhcTc) # toConstr :: AnnProvenance GhcTc -> Constr # dataTypeOf :: AnnProvenance GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnProvenance GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnProvenance GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> AnnProvenance GhcTc -> AnnProvenance GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnProvenance GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProvenance GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProvenance GhcTc -> m (AnnProvenance GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcTc -> m (AnnProvenance GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcTc -> m (AnnProvenance GhcTc) # | |
Data (AnnProvenance GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnProvenance GhcRn -> c (AnnProvenance GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnProvenance GhcRn) # toConstr :: AnnProvenance GhcRn -> Constr # dataTypeOf :: AnnProvenance GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnProvenance GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnProvenance GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> AnnProvenance GhcRn -> AnnProvenance GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnProvenance GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProvenance GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProvenance GhcRn -> m (AnnProvenance GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcRn -> m (AnnProvenance GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcRn -> m (AnnProvenance GhcRn) # | |
Data (AnnProvenance GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnProvenance GhcPs -> c (AnnProvenance GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnProvenance GhcPs) # toConstr :: AnnProvenance GhcPs -> Constr # dataTypeOf :: AnnProvenance GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnProvenance GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnProvenance GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> AnnProvenance GhcPs -> AnnProvenance GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnProvenance GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProvenance GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProvenance GhcPs -> m (AnnProvenance GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcPs -> m (AnnProvenance GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcPs -> m (AnnProvenance GhcPs) # | |
Data (AnnDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnDecl GhcTc -> c (AnnDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnDecl GhcTc) # toConstr :: AnnDecl GhcTc -> Constr # dataTypeOf :: AnnDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcTc -> AnnDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) # | |
Data (AnnDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnDecl GhcRn -> c (AnnDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnDecl GhcRn) # toConstr :: AnnDecl GhcRn -> Constr # dataTypeOf :: AnnDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcRn -> AnnDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) # | |
Data (AnnDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnDecl GhcPs -> c (AnnDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnDecl GhcPs) # toConstr :: AnnDecl GhcPs -> Constr # dataTypeOf :: AnnDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcPs -> AnnDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) # | |
Data (WarnDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcTc -> c (WarnDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcTc) # toConstr :: WarnDecl GhcTc -> Constr # dataTypeOf :: WarnDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcTc -> WarnDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) # | |
Data (WarnDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcRn -> c (WarnDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcRn) # toConstr :: WarnDecl GhcRn -> Constr # dataTypeOf :: WarnDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcRn -> WarnDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) # | |
Data (WarnDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcPs -> c (WarnDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcPs) # toConstr :: WarnDecl GhcPs -> Constr # dataTypeOf :: WarnDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcPs -> WarnDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) # | |
Data (WarnDecls GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcTc -> c (WarnDecls GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcTc) # toConstr :: WarnDecls GhcTc -> Constr # dataTypeOf :: WarnDecls GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcTc -> WarnDecls GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) # | |
Data (WarnDecls GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcRn -> c (WarnDecls GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcRn) # toConstr :: WarnDecls GhcRn -> Constr # dataTypeOf :: WarnDecls GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcRn -> WarnDecls GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) # | |
Data (WarnDecls GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcPs -> c (WarnDecls GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcPs) # toConstr :: WarnDecls GhcPs -> Constr # dataTypeOf :: WarnDecls GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcPs -> WarnDecls GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) # | |
Data (RuleBndr GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcTc -> c (RuleBndr GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcTc) # toConstr :: RuleBndr GhcTc -> Constr # dataTypeOf :: RuleBndr GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcTc -> RuleBndr GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) # | |
Data (RuleBndr GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcRn -> c (RuleBndr GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcRn) # toConstr :: RuleBndr GhcRn -> Constr # dataTypeOf :: RuleBndr GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcRn -> RuleBndr GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) # | |
Data (RuleBndr GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcPs -> c (RuleBndr GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcPs) # toConstr :: RuleBndr GhcPs -> Constr # dataTypeOf :: RuleBndr GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcPs -> RuleBndr GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) # | |
Data (RuleDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcTc -> c (RuleDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcTc) # toConstr :: RuleDecl GhcTc -> Constr # dataTypeOf :: RuleDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcTc -> RuleDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) # | |
Data (RuleDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcRn -> c (RuleDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcRn) # toConstr :: RuleDecl GhcRn -> Constr # dataTypeOf :: RuleDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcRn -> RuleDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) # | |
Data (RuleDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcPs -> c (RuleDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcPs) # toConstr :: RuleDecl GhcPs -> Constr # dataTypeOf :: RuleDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcPs -> RuleDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) # | |
Data (RuleDecls GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcTc -> c (RuleDecls GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcTc) # toConstr :: RuleDecls GhcTc -> Constr # dataTypeOf :: RuleDecls GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcTc -> RuleDecls GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) # | |
Data (RuleDecls GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcRn -> c (RuleDecls GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcRn) # toConstr :: RuleDecls GhcRn -> Constr # dataTypeOf :: RuleDecls GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcRn -> RuleDecls GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) # | |
Data (RuleDecls GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcPs -> c (RuleDecls GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcPs) # toConstr :: RuleDecls GhcPs -> Constr # dataTypeOf :: RuleDecls GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcPs -> RuleDecls GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) # | |
Data (ForeignDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignDecl GhcTc -> c (ForeignDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcTc) # toConstr :: ForeignDecl GhcTc -> Constr # dataTypeOf :: ForeignDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcTc -> ForeignDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) # | |
Data (ForeignDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignDecl GhcRn -> c (ForeignDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcRn) # toConstr :: ForeignDecl GhcRn -> Constr # dataTypeOf :: ForeignDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcRn -> ForeignDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) # | |
Data (ForeignDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignDecl GhcPs -> c (ForeignDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcPs) # toConstr :: ForeignDecl GhcPs -> Constr # dataTypeOf :: ForeignDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcPs -> ForeignDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) # | |
Data (DefaultDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultDecl GhcTc -> c (DefaultDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcTc) # toConstr :: DefaultDecl GhcTc -> Constr # dataTypeOf :: DefaultDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcTc -> DefaultDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) # | |
Data (DefaultDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultDecl GhcRn -> c (DefaultDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcRn) # toConstr :: DefaultDecl GhcRn -> Constr # dataTypeOf :: DefaultDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcRn -> DefaultDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) # | |
Data (DefaultDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefaultDecl GhcPs -> c (DefaultDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcPs) # toConstr :: DefaultDecl GhcPs -> Constr # dataTypeOf :: DefaultDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcPs -> DefaultDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) # | |
Data (DerivStrategy GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivStrategy GhcTc -> c (DerivStrategy GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcTc) # toConstr :: DerivStrategy GhcTc -> Constr # dataTypeOf :: DerivStrategy GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcTc -> DerivStrategy GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) # | |
Data (DerivStrategy GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivStrategy GhcRn -> c (DerivStrategy GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcRn) # toConstr :: DerivStrategy GhcRn -> Constr # dataTypeOf :: DerivStrategy GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcRn -> DerivStrategy GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) # | |
Data (DerivStrategy GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivStrategy GhcPs -> c (DerivStrategy GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcPs) # toConstr :: DerivStrategy GhcPs -> Constr # dataTypeOf :: DerivStrategy GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcPs -> DerivStrategy GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) # | |
Data (DerivDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivDecl GhcTc -> c (DerivDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcTc) # toConstr :: DerivDecl GhcTc -> Constr # dataTypeOf :: DerivDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcTc -> DerivDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) # | |
Data (DerivDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivDecl GhcRn -> c (DerivDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcRn) # toConstr :: DerivDecl GhcRn -> Constr # dataTypeOf :: DerivDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcRn -> DerivDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) # | |
Data (DerivDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivDecl GhcPs -> c (DerivDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcPs) # toConstr :: DerivDecl GhcPs -> Constr # dataTypeOf :: DerivDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcPs -> DerivDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) # | |
Data (InstDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcTc -> c (InstDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcTc) # toConstr :: InstDecl GhcTc -> Constr # dataTypeOf :: InstDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcTc -> InstDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) # | |
Data (InstDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcRn -> c (InstDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcRn) # toConstr :: InstDecl GhcRn -> Constr # dataTypeOf :: InstDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcRn -> InstDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) # | |
Data (InstDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcPs -> c (InstDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcPs) # toConstr :: InstDecl GhcPs -> Constr # dataTypeOf :: InstDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcPs -> InstDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) # | |
Data (ClsInstDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInstDecl GhcTc -> c (ClsInstDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcTc) # toConstr :: ClsInstDecl GhcTc -> Constr # dataTypeOf :: ClsInstDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcTc -> ClsInstDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) # | |
Data (ClsInstDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInstDecl GhcRn -> c (ClsInstDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcRn) # toConstr :: ClsInstDecl GhcRn -> Constr # dataTypeOf :: ClsInstDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcRn -> ClsInstDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) # | |
Data (ClsInstDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClsInstDecl GhcPs -> c (ClsInstDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcPs) # toConstr :: ClsInstDecl GhcPs -> Constr # dataTypeOf :: ClsInstDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcPs -> ClsInstDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) # | |
Data (DataFamInstDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataFamInstDecl GhcTc -> c (DataFamInstDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcTc) # toConstr :: DataFamInstDecl GhcTc -> Constr # dataTypeOf :: DataFamInstDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcTc -> DataFamInstDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) # | |
Data (DataFamInstDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataFamInstDecl GhcRn -> c (DataFamInstDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcRn) # toConstr :: DataFamInstDecl GhcRn -> Constr # dataTypeOf :: DataFamInstDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcRn -> DataFamInstDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) # | |
Data (DataFamInstDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataFamInstDecl GhcPs -> c (DataFamInstDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcPs) # toConstr :: DataFamInstDecl GhcPs -> Constr # dataTypeOf :: DataFamInstDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcPs -> DataFamInstDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) # | |
Data (TyFamInstDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcTc -> c (TyFamInstDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcTc) # toConstr :: TyFamInstDecl GhcTc -> Constr # dataTypeOf :: TyFamInstDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcTc -> TyFamInstDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) # | |
Data (TyFamInstDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcRn -> c (TyFamInstDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcRn) # toConstr :: TyFamInstDecl GhcRn -> Constr # dataTypeOf :: TyFamInstDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcRn -> TyFamInstDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) # | |
Data (TyFamInstDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcPs -> c (TyFamInstDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcPs) # toConstr :: TyFamInstDecl GhcPs -> Constr # dataTypeOf :: TyFamInstDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcPs -> TyFamInstDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) # | |
Data (HsConDeclGADTDetails GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDeclGADTDetails GhcTc -> c (HsConDeclGADTDetails GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDeclGADTDetails GhcTc) # toConstr :: HsConDeclGADTDetails GhcTc -> Constr # dataTypeOf :: HsConDeclGADTDetails GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDeclGADTDetails GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDeclGADTDetails GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsConDeclGADTDetails GhcTc -> HsConDeclGADTDetails GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcTc -> m (HsConDeclGADTDetails GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcTc -> m (HsConDeclGADTDetails GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcTc -> m (HsConDeclGADTDetails GhcTc) # | |
Data (HsConDeclGADTDetails GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDeclGADTDetails GhcRn -> c (HsConDeclGADTDetails GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDeclGADTDetails GhcRn) # toConstr :: HsConDeclGADTDetails GhcRn -> Constr # dataTypeOf :: HsConDeclGADTDetails GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDeclGADTDetails GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDeclGADTDetails GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsConDeclGADTDetails GhcRn -> HsConDeclGADTDetails GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcRn -> m (HsConDeclGADTDetails GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcRn -> m (HsConDeclGADTDetails GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcRn -> m (HsConDeclGADTDetails GhcRn) # | |
Data (HsConDeclGADTDetails GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDeclGADTDetails GhcPs -> c (HsConDeclGADTDetails GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDeclGADTDetails GhcPs) # toConstr :: HsConDeclGADTDetails GhcPs -> Constr # dataTypeOf :: HsConDeclGADTDetails GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDeclGADTDetails GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDeclGADTDetails GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsConDeclGADTDetails GhcPs -> HsConDeclGADTDetails GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcPs -> m (HsConDeclGADTDetails GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcPs -> m (HsConDeclGADTDetails GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcPs -> m (HsConDeclGADTDetails GhcPs) # | |
Data (ConDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDecl GhcTc -> c (ConDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcTc) # toConstr :: ConDecl GhcTc -> Constr # dataTypeOf :: ConDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcTc -> ConDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) # | |
Data (ConDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDecl GhcRn -> c (ConDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcRn) # toConstr :: ConDecl GhcRn -> Constr # dataTypeOf :: ConDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcRn -> ConDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) # | |
Data (ConDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDecl GhcPs -> c (ConDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcPs) # toConstr :: ConDecl GhcPs -> Constr # dataTypeOf :: ConDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcPs -> ConDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) # | |
Data (StandaloneKindSig GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StandaloneKindSig GhcTc -> c (StandaloneKindSig GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcTc) # toConstr :: StandaloneKindSig GhcTc -> Constr # dataTypeOf :: StandaloneKindSig GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcTc -> StandaloneKindSig GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) # | |
Data (StandaloneKindSig GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StandaloneKindSig GhcRn -> c (StandaloneKindSig GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcRn) # toConstr :: StandaloneKindSig GhcRn -> Constr # dataTypeOf :: StandaloneKindSig GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcRn -> StandaloneKindSig GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) # | |
Data (StandaloneKindSig GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StandaloneKindSig GhcPs -> c (StandaloneKindSig GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcPs) # toConstr :: StandaloneKindSig GhcPs -> Constr # dataTypeOf :: StandaloneKindSig GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcPs -> StandaloneKindSig GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) # | |
Data (DerivClauseTys GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivClauseTys GhcTc -> c (DerivClauseTys GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivClauseTys GhcTc) # toConstr :: DerivClauseTys GhcTc -> Constr # dataTypeOf :: DerivClauseTys GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivClauseTys GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivClauseTys GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> DerivClauseTys GhcTc -> DerivClauseTys GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivClauseTys GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivClauseTys GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcTc -> m (DerivClauseTys GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcTc -> m (DerivClauseTys GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcTc -> m (DerivClauseTys GhcTc) # | |
Data (DerivClauseTys GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivClauseTys GhcRn -> c (DerivClauseTys GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivClauseTys GhcRn) # toConstr :: DerivClauseTys GhcRn -> Constr # dataTypeOf :: DerivClauseTys GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivClauseTys GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivClauseTys GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> DerivClauseTys GhcRn -> DerivClauseTys GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivClauseTys GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivClauseTys GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcRn -> m (DerivClauseTys GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcRn -> m (DerivClauseTys GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcRn -> m (DerivClauseTys GhcRn) # | |
Data (DerivClauseTys GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DerivClauseTys GhcPs -> c (DerivClauseTys GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivClauseTys GhcPs) # toConstr :: DerivClauseTys GhcPs -> Constr # dataTypeOf :: DerivClauseTys GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivClauseTys GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivClauseTys GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> DerivClauseTys GhcPs -> DerivClauseTys GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> DerivClauseTys GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivClauseTys GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcPs -> m (DerivClauseTys GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcPs -> m (DerivClauseTys GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcPs -> m (DerivClauseTys GhcPs) # | |
Data (HsDerivingClause GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDerivingClause GhcTc -> c (HsDerivingClause GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcTc) # toConstr :: HsDerivingClause GhcTc -> Constr # dataTypeOf :: HsDerivingClause GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcTc -> HsDerivingClause GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) # | |
Data (HsDerivingClause GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDerivingClause GhcRn -> c (HsDerivingClause GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcRn) # toConstr :: HsDerivingClause GhcRn -> Constr # dataTypeOf :: HsDerivingClause GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcRn -> HsDerivingClause GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) # | |
Data (HsDerivingClause GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDerivingClause GhcPs -> c (HsDerivingClause GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcPs) # toConstr :: HsDerivingClause GhcPs -> Constr # dataTypeOf :: HsDerivingClause GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcPs -> HsDerivingClause GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) # | |
Data (HsDataDefn GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDataDefn GhcTc -> c (HsDataDefn GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcTc) # toConstr :: HsDataDefn GhcTc -> Constr # dataTypeOf :: HsDataDefn GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcTc -> HsDataDefn GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) # | |
Data (HsDataDefn GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDataDefn GhcRn -> c (HsDataDefn GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcRn) # toConstr :: HsDataDefn GhcRn -> Constr # dataTypeOf :: HsDataDefn GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcRn -> HsDataDefn GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) # | |
Data (HsDataDefn GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDataDefn GhcPs -> c (HsDataDefn GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcPs) # toConstr :: HsDataDefn GhcPs -> Constr # dataTypeOf :: HsDataDefn GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcPs -> HsDataDefn GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) # | |
Data (FamilyInfo GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyInfo GhcTc -> c (FamilyInfo GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcTc) # toConstr :: FamilyInfo GhcTc -> Constr # dataTypeOf :: FamilyInfo GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcTc -> FamilyInfo GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) # | |
Data (FamilyInfo GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyInfo GhcRn -> c (FamilyInfo GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcRn) # toConstr :: FamilyInfo GhcRn -> Constr # dataTypeOf :: FamilyInfo GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcRn -> FamilyInfo GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) # | |
Data (FamilyInfo GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyInfo GhcPs -> c (FamilyInfo GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcPs) # toConstr :: FamilyInfo GhcPs -> Constr # dataTypeOf :: FamilyInfo GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcPs -> FamilyInfo GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) # | |
Data (InjectivityAnn GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcTc -> c (InjectivityAnn GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcTc) # toConstr :: InjectivityAnn GhcTc -> Constr # dataTypeOf :: InjectivityAnn GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcTc -> InjectivityAnn GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) # | |
Data (InjectivityAnn GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcRn -> c (InjectivityAnn GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcRn) # toConstr :: InjectivityAnn GhcRn -> Constr # dataTypeOf :: InjectivityAnn GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcRn -> InjectivityAnn GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) # | |
Data (InjectivityAnn GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcPs -> c (InjectivityAnn GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcPs) # toConstr :: InjectivityAnn GhcPs -> Constr # dataTypeOf :: InjectivityAnn GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcPs -> InjectivityAnn GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) # | |
Data (FamilyDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyDecl GhcTc -> c (FamilyDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcTc) # toConstr :: FamilyDecl GhcTc -> Constr # dataTypeOf :: FamilyDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcTc -> FamilyDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) # | |
Data (FamilyDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyDecl GhcRn -> c (FamilyDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcRn) # toConstr :: FamilyDecl GhcRn -> Constr # dataTypeOf :: FamilyDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcRn -> FamilyDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) # | |
Data (FamilyDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyDecl GhcPs -> c (FamilyDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcPs) # toConstr :: FamilyDecl GhcPs -> Constr # dataTypeOf :: FamilyDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcPs -> FamilyDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) # | |
Data (FamilyResultSig GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyResultSig GhcTc -> c (FamilyResultSig GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcTc) # toConstr :: FamilyResultSig GhcTc -> Constr # dataTypeOf :: FamilyResultSig GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcTc -> FamilyResultSig GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) # | |
Data (FamilyResultSig GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyResultSig GhcRn -> c (FamilyResultSig GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcRn) # toConstr :: FamilyResultSig GhcRn -> Constr # dataTypeOf :: FamilyResultSig GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcRn -> FamilyResultSig GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) # | |
Data (FamilyResultSig GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamilyResultSig GhcPs -> c (FamilyResultSig GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcPs) # toConstr :: FamilyResultSig GhcPs -> Constr # dataTypeOf :: FamilyResultSig GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcPs -> FamilyResultSig GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) # | |
Data (TyClGroup GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcTc -> c (TyClGroup GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcTc) # toConstr :: TyClGroup GhcTc -> Constr # dataTypeOf :: TyClGroup GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcTc -> TyClGroup GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) # | |
Data (TyClGroup GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcRn -> c (TyClGroup GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcRn) # toConstr :: TyClGroup GhcRn -> Constr # dataTypeOf :: TyClGroup GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcRn -> TyClGroup GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) # | |
Data (TyClGroup GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcPs -> c (TyClGroup GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcPs) # toConstr :: TyClGroup GhcPs -> Constr # dataTypeOf :: TyClGroup GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcPs -> TyClGroup GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) # | |
Data (FunDep GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunDep GhcTc -> c (FunDep GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FunDep GhcTc) # toConstr :: FunDep GhcTc -> Constr # dataTypeOf :: FunDep GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FunDep GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FunDep GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> FunDep GhcTc -> FunDep GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> FunDep GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep GhcTc -> m (FunDep GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcTc -> m (FunDep GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcTc -> m (FunDep GhcTc) # | |
Data (FunDep GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunDep GhcRn -> c (FunDep GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FunDep GhcRn) # toConstr :: FunDep GhcRn -> Constr # dataTypeOf :: FunDep GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FunDep GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FunDep GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> FunDep GhcRn -> FunDep GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> FunDep GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep GhcRn -> m (FunDep GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcRn -> m (FunDep GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcRn -> m (FunDep GhcRn) # | |
Data (FunDep GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunDep GhcPs -> c (FunDep GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FunDep GhcPs) # toConstr :: FunDep GhcPs -> Constr # dataTypeOf :: FunDep GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FunDep GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FunDep GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> FunDep GhcPs -> FunDep GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> FunDep GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep GhcPs -> m (FunDep GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcPs -> m (FunDep GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcPs -> m (FunDep GhcPs) # | |
Data (TyClDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcTc -> c (TyClDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcTc) # toConstr :: TyClDecl GhcTc -> Constr # dataTypeOf :: TyClDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcTc -> TyClDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) # | |
Data (TyClDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcRn -> c (TyClDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcRn) # toConstr :: TyClDecl GhcRn -> Constr # dataTypeOf :: TyClDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcRn -> TyClDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) # | |
Data (TyClDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcPs -> c (TyClDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcPs) # toConstr :: TyClDecl GhcPs -> Constr # dataTypeOf :: TyClDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcPs -> TyClDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) # | |
Data (SpliceDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcTc -> c (SpliceDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcTc) # toConstr :: SpliceDecl GhcTc -> Constr # dataTypeOf :: SpliceDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcTc -> SpliceDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) # | |
Data (SpliceDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcRn -> c (SpliceDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcRn) # toConstr :: SpliceDecl GhcRn -> Constr # dataTypeOf :: SpliceDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcRn -> SpliceDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) # | |
Data (SpliceDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcPs -> c (SpliceDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcPs) # toConstr :: SpliceDecl GhcPs -> Constr # dataTypeOf :: SpliceDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcPs -> SpliceDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) # | |
Data (HsGroup GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGroup GhcTc -> c (HsGroup GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcTc) # toConstr :: HsGroup GhcTc -> Constr # dataTypeOf :: HsGroup GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcTc -> HsGroup GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) # | |
Data (HsGroup GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGroup GhcRn -> c (HsGroup GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcRn) # toConstr :: HsGroup GhcRn -> Constr # dataTypeOf :: HsGroup GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcRn -> HsGroup GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) # | |
Data (HsGroup GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGroup GhcPs -> c (HsGroup GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcPs) # toConstr :: HsGroup GhcPs -> Constr # dataTypeOf :: HsGroup GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcPs -> HsGroup GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) # | |
Data (HsDecl GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDecl GhcTc -> c (HsDecl GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcTc) # toConstr :: HsDecl GhcTc -> Constr # dataTypeOf :: HsDecl GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcTc -> HsDecl GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) # | |
Data (HsDecl GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDecl GhcRn -> c (HsDecl GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcRn) # toConstr :: HsDecl GhcRn -> Constr # dataTypeOf :: HsDecl GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcRn -> HsDecl GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) # | |
Data (HsDecl GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsDecl GhcPs -> c (HsDecl GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcPs) # toConstr :: HsDecl GhcPs -> Constr # dataTypeOf :: HsDecl GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcPs -> HsDecl GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) # | |
Data (HsStmtContext GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsStmtContext GhcTc -> c (HsStmtContext GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext GhcTc) # toConstr :: HsStmtContext GhcTc -> Constr # dataTypeOf :: HsStmtContext GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsStmtContext GhcTc -> HsStmtContext GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext GhcTc -> m (HsStmtContext GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcTc -> m (HsStmtContext GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcTc -> m (HsStmtContext GhcTc) # | |
Data (HsStmtContext GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsStmtContext GhcRn -> c (HsStmtContext GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext GhcRn) # toConstr :: HsStmtContext GhcRn -> Constr # dataTypeOf :: HsStmtContext GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsStmtContext GhcRn -> HsStmtContext GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext GhcRn -> m (HsStmtContext GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcRn -> m (HsStmtContext GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcRn -> m (HsStmtContext GhcRn) # | |
Data (HsStmtContext GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsStmtContext GhcPs -> c (HsStmtContext GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext GhcPs) # toConstr :: HsStmtContext GhcPs -> Constr # dataTypeOf :: HsStmtContext GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsStmtContext GhcPs -> HsStmtContext GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext GhcPs -> m (HsStmtContext GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcPs -> m (HsStmtContext GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcPs -> m (HsStmtContext GhcPs) # | |
Data (HsMatchContext GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsMatchContext GhcTc -> c (HsMatchContext GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext GhcTc) # toConstr :: HsMatchContext GhcTc -> Constr # dataTypeOf :: HsMatchContext GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsMatchContext GhcTc -> HsMatchContext GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext GhcTc -> m (HsMatchContext GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcTc -> m (HsMatchContext GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcTc -> m (HsMatchContext GhcTc) # | |
Data (HsMatchContext GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsMatchContext GhcRn -> c (HsMatchContext GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext GhcRn) # toConstr :: HsMatchContext GhcRn -> Constr # dataTypeOf :: HsMatchContext GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsMatchContext GhcRn -> HsMatchContext GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext GhcRn -> m (HsMatchContext GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcRn -> m (HsMatchContext GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcRn -> m (HsMatchContext GhcRn) # | |
Data (HsMatchContext GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsMatchContext GhcPs -> c (HsMatchContext GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext GhcPs) # toConstr :: HsMatchContext GhcPs -> Constr # dataTypeOf :: HsMatchContext GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsMatchContext GhcPs -> HsMatchContext GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext GhcPs -> m (HsMatchContext GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcPs -> m (HsMatchContext GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcPs -> m (HsMatchContext GhcPs) # | |
Data (ArithSeqInfo GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcTc -> c (ArithSeqInfo GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcTc) # toConstr :: ArithSeqInfo GhcTc -> Constr # dataTypeOf :: ArithSeqInfo GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcTc -> ArithSeqInfo GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) # | |
Data (ArithSeqInfo GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcRn -> c (ArithSeqInfo GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcRn) # toConstr :: ArithSeqInfo GhcRn -> Constr # dataTypeOf :: ArithSeqInfo GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcRn -> ArithSeqInfo GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) # | |
Data (ArithSeqInfo GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcPs -> c (ArithSeqInfo GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcPs) # toConstr :: ArithSeqInfo GhcPs -> Constr # dataTypeOf :: ArithSeqInfo GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcPs -> ArithSeqInfo GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) # | |
Data (HsBracket GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcTc -> c (HsBracket GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcTc) # toConstr :: HsBracket GhcTc -> Constr # dataTypeOf :: HsBracket GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcTc -> HsBracket GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) # | |
Data (HsBracket GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcRn -> c (HsBracket GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcRn) # toConstr :: HsBracket GhcRn -> Constr # dataTypeOf :: HsBracket GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcRn -> HsBracket GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) # | |
Data (HsBracket GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcPs -> c (HsBracket GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcPs) # toConstr :: HsBracket GhcPs -> Constr # dataTypeOf :: HsBracket GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcPs -> HsBracket GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) # | |
Data (HsSplicedThing GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcTc -> c (HsSplicedThing GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcTc) # toConstr :: HsSplicedThing GhcTc -> Constr # dataTypeOf :: HsSplicedThing GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcTc -> HsSplicedThing GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) # | |
Data (HsSplicedThing GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcRn -> c (HsSplicedThing GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcRn) # toConstr :: HsSplicedThing GhcRn -> Constr # dataTypeOf :: HsSplicedThing GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcRn -> HsSplicedThing GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) # | |
Data (HsSplicedThing GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcPs -> c (HsSplicedThing GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcPs) # toConstr :: HsSplicedThing GhcPs -> Constr # dataTypeOf :: HsSplicedThing GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcPs -> HsSplicedThing GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) # | |
Data (ApplicativeArg GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcTc -> c (ApplicativeArg GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcTc) # toConstr :: ApplicativeArg GhcTc -> Constr # dataTypeOf :: ApplicativeArg GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcTc -> ApplicativeArg GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) # | |
Data (ApplicativeArg GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcRn -> c (ApplicativeArg GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcRn) # toConstr :: ApplicativeArg GhcRn -> Constr # dataTypeOf :: ApplicativeArg GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcRn -> ApplicativeArg GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) # | |
Data (ApplicativeArg GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcPs -> c (ApplicativeArg GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcPs) # toConstr :: ApplicativeArg GhcPs -> Constr # dataTypeOf :: ApplicativeArg GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcPs -> ApplicativeArg GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) # | |
Data (HsCmdTop GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcTc -> c (HsCmdTop GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcTc) # toConstr :: HsCmdTop GhcTc -> Constr # dataTypeOf :: HsCmdTop GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcTc -> HsCmdTop GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) # | |
Data (HsCmdTop GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcRn -> c (HsCmdTop GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcRn) # toConstr :: HsCmdTop GhcRn -> Constr # dataTypeOf :: HsCmdTop GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcRn -> HsCmdTop GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) # | |
Data (HsCmdTop GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcPs -> c (HsCmdTop GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcPs) # toConstr :: HsCmdTop GhcPs -> Constr # dataTypeOf :: HsCmdTop GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcPs -> HsCmdTop GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) # | |
Data (HsCmd GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcTc -> c (HsCmd GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcTc) # toConstr :: HsCmd GhcTc -> Constr # dataTypeOf :: HsCmd GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcTc -> HsCmd GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) # | |
Data (HsCmd GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcRn -> c (HsCmd GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcRn) # toConstr :: HsCmd GhcRn -> Constr # dataTypeOf :: HsCmd GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcRn -> HsCmd GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) # | |
Data (HsCmd GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcPs -> c (HsCmd GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcPs) # toConstr :: HsCmd GhcPs -> Constr # dataTypeOf :: HsCmd GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcPs -> HsCmd GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) # | |
Data (HsTupArg GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcTc -> c (HsTupArg GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcTc) # toConstr :: HsTupArg GhcTc -> Constr # dataTypeOf :: HsTupArg GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcTc -> HsTupArg GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) # | |
Data (HsTupArg GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcRn -> c (HsTupArg GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcRn) # toConstr :: HsTupArg GhcRn -> Constr # dataTypeOf :: HsTupArg GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcRn -> HsTupArg GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) # | |
Data (HsTupArg GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcPs -> c (HsTupArg GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcPs) # toConstr :: HsTupArg GhcPs -> Constr # dataTypeOf :: HsTupArg GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcPs -> HsTupArg GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) # | |
Data (HsPragE GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPragE GhcTc -> c (HsPragE GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPragE GhcTc) # toConstr :: HsPragE GhcTc -> Constr # dataTypeOf :: HsPragE GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPragE GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPragE GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsPragE GhcTc -> HsPragE GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPragE GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPragE GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPragE GhcTc -> m (HsPragE GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcTc -> m (HsPragE GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcTc -> m (HsPragE GhcTc) # | |
Data (HsPragE GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPragE GhcRn -> c (HsPragE GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPragE GhcRn) # toConstr :: HsPragE GhcRn -> Constr # dataTypeOf :: HsPragE GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPragE GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPragE GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsPragE GhcRn -> HsPragE GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPragE GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPragE GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPragE GhcRn -> m (HsPragE GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcRn -> m (HsPragE GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcRn -> m (HsPragE GhcRn) # | |
Data (HsPragE GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPragE GhcPs -> c (HsPragE GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPragE GhcPs) # toConstr :: HsPragE GhcPs -> Constr # dataTypeOf :: HsPragE GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPragE GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPragE GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsPragE GhcPs -> HsPragE GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPragE GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPragE GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPragE GhcPs -> m (HsPragE GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcPs -> m (HsPragE GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcPs -> m (HsPragE GhcPs) # | |
Data (HsFieldLabel GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsFieldLabel GhcTc -> c (HsFieldLabel GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsFieldLabel GhcTc) # toConstr :: HsFieldLabel GhcTc -> Constr # dataTypeOf :: HsFieldLabel GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsFieldLabel GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsFieldLabel GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsFieldLabel GhcTc -> HsFieldLabel GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldLabel GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldLabel GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsFieldLabel GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsFieldLabel GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcTc -> m (HsFieldLabel GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcTc -> m (HsFieldLabel GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcTc -> m (HsFieldLabel GhcTc) # | |
Data (HsFieldLabel GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsFieldLabel GhcRn -> c (HsFieldLabel GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsFieldLabel GhcRn) # toConstr :: HsFieldLabel GhcRn -> Constr # dataTypeOf :: HsFieldLabel GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsFieldLabel GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsFieldLabel GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsFieldLabel GhcRn -> HsFieldLabel GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldLabel GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldLabel GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsFieldLabel GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsFieldLabel GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcRn -> m (HsFieldLabel GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcRn -> m (HsFieldLabel GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcRn -> m (HsFieldLabel GhcRn) # | |
Data (HsFieldLabel GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsFieldLabel GhcPs -> c (HsFieldLabel GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsFieldLabel GhcPs) # toConstr :: HsFieldLabel GhcPs -> Constr # dataTypeOf :: HsFieldLabel GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsFieldLabel GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsFieldLabel GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsFieldLabel GhcPs -> HsFieldLabel GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldLabel GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldLabel GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsFieldLabel GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsFieldLabel GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcPs -> m (HsFieldLabel GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcPs -> m (HsFieldLabel GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldLabel GhcPs -> m (HsFieldLabel GhcPs) # | |
Data (FieldLabelStrings GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLabelStrings GhcTc -> c (FieldLabelStrings GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLabelStrings GhcTc) # toConstr :: FieldLabelStrings GhcTc -> Constr # dataTypeOf :: FieldLabelStrings GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLabelStrings GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLabelStrings GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> FieldLabelStrings GhcTc -> FieldLabelStrings GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldLabelStrings GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLabelStrings GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcTc -> m (FieldLabelStrings GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcTc -> m (FieldLabelStrings GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcTc -> m (FieldLabelStrings GhcTc) # | |
Data (FieldLabelStrings GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLabelStrings GhcRn -> c (FieldLabelStrings GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLabelStrings GhcRn) # toConstr :: FieldLabelStrings GhcRn -> Constr # dataTypeOf :: FieldLabelStrings GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLabelStrings GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLabelStrings GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> FieldLabelStrings GhcRn -> FieldLabelStrings GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldLabelStrings GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLabelStrings GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcRn -> m (FieldLabelStrings GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcRn -> m (FieldLabelStrings GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcRn -> m (FieldLabelStrings GhcRn) # | |
Data (FieldLabelStrings GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLabelStrings GhcPs -> c (FieldLabelStrings GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLabelStrings GhcPs) # toConstr :: FieldLabelStrings GhcPs -> Constr # dataTypeOf :: FieldLabelStrings GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLabelStrings GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLabelStrings GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> FieldLabelStrings GhcPs -> FieldLabelStrings GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldLabelStrings GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLabelStrings GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcPs -> m (FieldLabelStrings GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcPs -> m (FieldLabelStrings GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcPs -> m (FieldLabelStrings GhcPs) # | |
Data (NHsValBindsLR GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcTc -> c (NHsValBindsLR GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcTc) # toConstr :: NHsValBindsLR GhcTc -> Constr # dataTypeOf :: NHsValBindsLR GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcTc -> NHsValBindsLR GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) # | |
Data (NHsValBindsLR GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcRn -> c (NHsValBindsLR GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcRn) # toConstr :: NHsValBindsLR GhcRn -> Constr # dataTypeOf :: NHsValBindsLR GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcRn -> NHsValBindsLR GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) # | |
Data (NHsValBindsLR GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NHsValBindsLR GhcPs -> c (NHsValBindsLR GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcPs) # toConstr :: NHsValBindsLR GhcPs -> Constr # dataTypeOf :: NHsValBindsLR GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcPs -> NHsValBindsLR GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) # | |
OutputableBndr (AmbiguousFieldOcc (GhcPass p)) Source # | |
Defined in GHC.Hs.Type pprBndr :: BindingSite -> AmbiguousFieldOcc (GhcPass p) -> SDoc Source # pprPrefixOcc :: AmbiguousFieldOcc (GhcPass p) -> SDoc Source # pprInfixOcc :: AmbiguousFieldOcc (GhcPass p) -> SDoc Source # bndrIsJoin_maybe :: AmbiguousFieldOcc (GhcPass p) -> Maybe Int Source # | |
OutputableBndrId p => Outputable (HsSplice (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsExpr (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (IE (GhcPass p)) Source # | |
(OutputableBndrId p, Outputable (Anno (IE (GhcPass p)))) => Outputable (ImportDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.ImpExp | |
OutputableBndrId p => Outputable (HsOverLit (GhcPass p)) Source # | |
Outputable (HsLit (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (Pat (GhcPass p)) Source # | |
Outputable (AmbiguousFieldOcc (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
OutputableBndrId pass => Outputable (HsArrow (GhcPass pass)) Source # | |
OutputableBndrId p => Outputable (HsType (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsSigType (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsPatSigType (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
OutputableBndrId p => Outputable (HsForAllTelescope (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
OutputableBndrId p => Outputable (FixitySig (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (Sig (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (IPBind (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsIPBinds (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (ABExport (GhcPass p)) Source # | |
OutputableBndr (IdP (GhcPass p)) => Outputable (RoleAnnotDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (AnnDecl (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (WarnDecl (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (WarnDecls (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (RuleBndr (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (RuleDecl (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (RuleDecls (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (ForeignDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (DefaultDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (DerivStrategy (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (DerivDecl (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (InstDecl (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (ClsInstDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (DataFamInstDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (TyFamInstDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (ConDecl (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (StandaloneKindSig (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (DerivClauseTys (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (HsDerivingClause (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (HsDataDefn (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (FamilyDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (TyClGroup (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (FunDep (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (TyClDecl (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (SpliceDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
OutputableBndrId p => Outputable (HsGroup (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsDecl (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsStmtContext (GhcPass p)) Source # | |
Defined in GHC.Hs.Expr | |
OutputableBndrId p => Outputable (HsMatchContext (GhcPass p)) Source # | |
Defined in GHC.Hs.Expr | |
OutputableBndrId p => Outputable (ArithSeqInfo (GhcPass p)) Source # | |
Defined in GHC.Hs.Expr | |
OutputableBndrId p => Outputable (HsBracket (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsSplicedThing (GhcPass p)) Source # | |
Defined in GHC.Hs.Expr | |
OutputableBndrId idL => Outputable (ApplicativeArg (GhcPass idL)) Source # | |
Defined in GHC.Hs.Expr | |
OutputableBndrId p => Outputable (HsCmdTop (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsCmd (GhcPass p)) Source # | |
Outputable (HsPragE (GhcPass p)) Source # | |
Outputable (PatBuilder GhcPs) Source # | |
Defined in GHC.Parser.Types | |
MapXRec (GhcPass p) Source # | |
UnXRec (GhcPass p) Source # | |
IsPass p => CollectPass (GhcPass p) Source # | |
Defined in GHC.Hs.Utils | |
DisambTD (HsType GhcPs) Source # | |
Defined in GHC.Parser.PostProcess mkHsAppTyHeadPV :: LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkHsAppTyPV :: LocatedA (HsType GhcPs) -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkHsAppKindTyPV :: LocatedA (HsType GhcPs) -> SrcSpan -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkHsOpTyPV :: LHsType GhcPs -> LocatedN RdrName -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkUnpackednessPV :: Located UnpackednessPragma -> LocatedA (HsType GhcPs) -> PV (LocatedA (HsType GhcPs)) Source # | |
DisambECP (HsExpr GhcPs) Source # | |
Defined in GHC.Parser.PostProcess ecpFromCmd' :: LHsCmd GhcPs -> PV (LocatedA (HsExpr GhcPs)) Source # ecpFromExp' :: LHsExpr GhcPs -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsProjUpdatePV :: SrcSpan -> Located [Located (HsFieldLabel GhcPs)] -> LocatedA (HsExpr GhcPs) -> Bool -> [AddEpAnn] -> PV (LHsRecProj GhcPs (LocatedA (HsExpr GhcPs))) Source # mkHsLamPV :: SrcSpan -> (EpAnnComments -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsLetPV :: SrcSpan -> HsLocalBinds GhcPs -> LocatedA (HsExpr GhcPs) -> AnnsLet -> PV (LocatedA (HsExpr GhcPs)) Source # superInfixOp :: (DisambInfixOp (InfixOp (HsExpr GhcPs)) => PV (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsOpAppPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> LocatedN (InfixOp (HsExpr GhcPs)) -> LocatedA (HsExpr GhcPs) -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> LocatedL [LMatch GhcPs (LocatedA (HsExpr GhcPs))] -> EpAnnHsCase -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsLamCasePV :: SrcSpan -> LocatedL [LMatch GhcPs (LocatedA (HsExpr GhcPs))] -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # superFunArg :: (DisambECP (FunArg (HsExpr GhcPs)) => PV (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsAppPV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> LocatedA (FunArg (HsExpr GhcPs)) -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsAppTypePV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> SrcSpan -> LHsType GhcPs -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> LocatedA (HsExpr GhcPs) -> Bool -> LocatedA (HsExpr GhcPs) -> AnnsIf -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsDoPV :: SrcSpan -> Maybe ModuleName -> LocatedL [LStmt GhcPs (LocatedA (HsExpr GhcPs))] -> AnnList -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsParPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> AnnParen -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsExpr GhcPs)) Source # mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (HsExpr GhcPs)) Source # mkHsWildCardPV :: SrcSpan -> PV (Located (HsExpr GhcPs)) Source # mkHsTySigPV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> LHsType GhcPs -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsExplicitListPV :: SrcSpan -> [LocatedA (HsExpr GhcPs)] -> AnnList -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (HsExpr GhcPs)) Source # mkHsRecordPV :: Bool -> SrcSpan -> SrcSpan -> LocatedA (HsExpr GhcPs) -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsNegAppPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsSectionR_PV :: SrcSpan -> LocatedA (InfixOp (HsExpr GhcPs)) -> LocatedA (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source # mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsAsPatPV :: SrcSpan -> LocatedN RdrName -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsLazyPatPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsBangPatPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # mkSumOrTuplePV :: SrcSpanAnnA -> Boxity -> SumOrTuple (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) Source # | |
DisambECP (HsCmd GhcPs) Source # | |
Defined in GHC.Parser.PostProcess ecpFromCmd' :: LHsCmd GhcPs -> PV (LocatedA (HsCmd GhcPs)) Source # ecpFromExp' :: LHsExpr GhcPs -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsProjUpdatePV :: SrcSpan -> Located [Located (HsFieldLabel GhcPs)] -> LocatedA (HsCmd GhcPs) -> Bool -> [AddEpAnn] -> PV (LHsRecProj GhcPs (LocatedA (HsCmd GhcPs))) Source # mkHsLamPV :: SrcSpan -> (EpAnnComments -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsLetPV :: SrcSpan -> HsLocalBinds GhcPs -> LocatedA (HsCmd GhcPs) -> AnnsLet -> PV (LocatedA (HsCmd GhcPs)) Source # superInfixOp :: (DisambInfixOp (InfixOp (HsCmd GhcPs)) => PV (LocatedA (HsCmd GhcPs))) -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsOpAppPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> LocatedN (InfixOp (HsCmd GhcPs)) -> LocatedA (HsCmd GhcPs) -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> LocatedL [LMatch GhcPs (LocatedA (HsCmd GhcPs))] -> EpAnnHsCase -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsLamCasePV :: SrcSpan -> LocatedL [LMatch GhcPs (LocatedA (HsCmd GhcPs))] -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # superFunArg :: (DisambECP (FunArg (HsCmd GhcPs)) => PV (LocatedA (HsCmd GhcPs))) -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsAppPV :: SrcSpanAnnA -> LocatedA (HsCmd GhcPs) -> LocatedA (FunArg (HsCmd GhcPs)) -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsAppTypePV :: SrcSpanAnnA -> LocatedA (HsCmd GhcPs) -> SrcSpan -> LHsType GhcPs -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> LocatedA (HsCmd GhcPs) -> Bool -> LocatedA (HsCmd GhcPs) -> AnnsIf -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsDoPV :: SrcSpan -> Maybe ModuleName -> LocatedL [LStmt GhcPs (LocatedA (HsCmd GhcPs))] -> AnnList -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsParPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> AnnParen -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsCmd GhcPs)) Source # mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (HsCmd GhcPs)) Source # mkHsWildCardPV :: SrcSpan -> PV (Located (HsCmd GhcPs)) Source # mkHsTySigPV :: SrcSpanAnnA -> LocatedA (HsCmd GhcPs) -> LHsType GhcPs -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsExplicitListPV :: SrcSpan -> [LocatedA (HsCmd GhcPs)] -> AnnList -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (HsCmd GhcPs)) Source # mkHsRecordPV :: Bool -> SrcSpan -> SrcSpan -> LocatedA (HsCmd GhcPs) -> ([Fbind (HsCmd GhcPs)], Maybe SrcSpan) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsNegAppPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsSectionR_PV :: SrcSpan -> LocatedA (InfixOp (HsCmd GhcPs)) -> LocatedA (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source # mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsAsPatPV :: SrcSpan -> LocatedN RdrName -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsLazyPatPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsBangPatPV :: SrcSpan -> LocatedA (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # mkSumOrTuplePV :: SrcSpanAnnA -> Boxity -> SumOrTuple (HsCmd GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsCmd GhcPs)) Source # | |
DisambECP (PatBuilder GhcPs) Source # | |
Defined in GHC.Parser.PostProcess type Body (PatBuilder GhcPs) :: Type -> Type Source # type InfixOp (PatBuilder GhcPs) Source # type FunArg (PatBuilder GhcPs) Source # ecpFromCmd' :: LHsCmd GhcPs -> PV (LocatedA (PatBuilder GhcPs)) Source # ecpFromExp' :: LHsExpr GhcPs -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsProjUpdatePV :: SrcSpan -> Located [Located (HsFieldLabel GhcPs)] -> LocatedA (PatBuilder GhcPs) -> Bool -> [AddEpAnn] -> PV (LHsRecProj GhcPs (LocatedA (PatBuilder GhcPs))) Source # mkHsLamPV :: SrcSpan -> (EpAnnComments -> MatchGroup GhcPs (LocatedA (PatBuilder GhcPs))) -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsLetPV :: SrcSpan -> HsLocalBinds GhcPs -> LocatedA (PatBuilder GhcPs) -> AnnsLet -> PV (LocatedA (PatBuilder GhcPs)) Source # superInfixOp :: (DisambInfixOp (InfixOp (PatBuilder GhcPs)) => PV (LocatedA (PatBuilder GhcPs))) -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsOpAppPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> LocatedN (InfixOp (PatBuilder GhcPs)) -> LocatedA (PatBuilder GhcPs) -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> LocatedL [LMatch GhcPs (LocatedA (PatBuilder GhcPs))] -> EpAnnHsCase -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsLamCasePV :: SrcSpan -> LocatedL [LMatch GhcPs (LocatedA (PatBuilder GhcPs))] -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # superFunArg :: (DisambECP (FunArg (PatBuilder GhcPs)) => PV (LocatedA (PatBuilder GhcPs))) -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsAppPV :: SrcSpanAnnA -> LocatedA (PatBuilder GhcPs) -> LocatedA (FunArg (PatBuilder GhcPs)) -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsAppTypePV :: SrcSpanAnnA -> LocatedA (PatBuilder GhcPs) -> SrcSpan -> LHsType GhcPs -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> LocatedA (PatBuilder GhcPs) -> Bool -> LocatedA (PatBuilder GhcPs) -> AnnsIf -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsDoPV :: SrcSpan -> Maybe ModuleName -> LocatedL [LStmt GhcPs (LocatedA (PatBuilder GhcPs))] -> AnnList -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsParPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> AnnParen -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (PatBuilder GhcPs)) Source # mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (PatBuilder GhcPs)) Source # mkHsWildCardPV :: SrcSpan -> PV (Located (PatBuilder GhcPs)) Source # mkHsTySigPV :: SrcSpanAnnA -> LocatedA (PatBuilder GhcPs) -> LHsType GhcPs -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsExplicitListPV :: SrcSpan -> [LocatedA (PatBuilder GhcPs)] -> AnnList -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (PatBuilder GhcPs)) Source # mkHsRecordPV :: Bool -> SrcSpan -> SrcSpan -> LocatedA (PatBuilder GhcPs) -> ([Fbind (PatBuilder GhcPs)], Maybe SrcSpan) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsNegAppPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsSectionR_PV :: SrcSpan -> LocatedA (InfixOp (PatBuilder GhcPs)) -> LocatedA (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source # mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsAsPatPV :: SrcSpan -> LocatedN RdrName -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsLazyPatPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsBangPatPV :: SrcSpan -> LocatedA (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # mkSumOrTuplePV :: SrcSpanAnnA -> Boxity -> SumOrTuple (PatBuilder GhcPs) -> [AddEpAnn] -> PV (LocatedA (PatBuilder GhcPs)) Source # rejectPragmaPV :: LocatedA (PatBuilder GhcPs) -> PV () Source # | |
DisambInfixOp (HsExpr GhcPs) Source # | |
Defined in GHC.Parser.PostProcess | |
Anno a ~ SrcSpanAnn' (EpAnn an) => WrapXRec (GhcPass p) a Source # | |
Data (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) # toConstr :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> Constr # dataTypeOf :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) # | |
Data (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) # toConstr :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> Constr # dataTypeOf :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) # | |
Data (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) # toConstr :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr # dataTypeOf :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) # | |
Data (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) # toConstr :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr # dataTypeOf :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) # | |
Data (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) # toConstr :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr # dataTypeOf :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) # | |
Data (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) # toConstr :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr # dataTypeOf :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) # | |
Data (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) # toConstr :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> Constr # dataTypeOf :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) # | |
Data (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) # toConstr :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> Constr # dataTypeOf :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) # | |
Data (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) # toConstr :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> Constr # dataTypeOf :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) # | |
Data (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) # toConstr :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> Constr # dataTypeOf :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) # | |
Data (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) # toConstr :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Constr # dataTypeOf :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) # | |
Data (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) # toConstr :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Constr # dataTypeOf :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) # | |
Data thing => Data (HsScaled GhcTc thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcTc thing -> c (HsScaled GhcTc thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcTc thing) # toConstr :: HsScaled GhcTc thing -> Constr # dataTypeOf :: HsScaled GhcTc thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcTc thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcTc thing)) # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcTc thing -> HsScaled GhcTc thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcTc thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcTc thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcTc thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcTc thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) # | |
Data thing => Data (HsScaled GhcRn thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcRn thing -> c (HsScaled GhcRn thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcRn thing) # toConstr :: HsScaled GhcRn thing -> Constr # dataTypeOf :: HsScaled GhcRn thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcRn thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcRn thing)) # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcRn thing -> HsScaled GhcRn thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcRn thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcRn thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcRn thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcRn thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) # | |
Data thing => Data (HsScaled GhcPs thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcPs thing -> c (HsScaled GhcPs thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcPs thing) # toConstr :: HsScaled GhcPs thing -> Constr # dataTypeOf :: HsScaled GhcPs thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcPs thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcPs thing)) # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcPs thing -> HsScaled GhcPs thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcPs thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcPs thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcPs thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcPs thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) # | |
Data flag => Data (HsTyVarBndr flag GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcTc -> c (HsTyVarBndr flag GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcTc) # toConstr :: HsTyVarBndr flag GhcTc -> Constr # dataTypeOf :: HsTyVarBndr flag GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcTc -> HsTyVarBndr flag GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) # | |
Data flag => Data (HsTyVarBndr flag GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcRn -> c (HsTyVarBndr flag GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcRn) # toConstr :: HsTyVarBndr flag GhcRn -> Constr # dataTypeOf :: HsTyVarBndr flag GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcRn -> HsTyVarBndr flag GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) # | |
Data flag => Data (HsTyVarBndr flag GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcPs -> c (HsTyVarBndr flag GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcPs) # toConstr :: HsTyVarBndr flag GhcPs -> Constr # dataTypeOf :: HsTyVarBndr flag GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcPs -> HsTyVarBndr flag GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) # | |
Data thing => Data (HsWildCardBndrs GhcTc thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcTc thing -> c (HsWildCardBndrs GhcTc thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcTc thing) # toConstr :: HsWildCardBndrs GhcTc thing -> Constr # dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcTc thing -> HsWildCardBndrs GhcTc thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) # | |
Data thing => Data (HsWildCardBndrs GhcRn thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcRn thing -> c (HsWildCardBndrs GhcRn thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcRn thing) # toConstr :: HsWildCardBndrs GhcRn thing -> Constr # dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcRn thing -> HsWildCardBndrs GhcRn thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) # | |
Data thing => Data (HsWildCardBndrs GhcPs thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcPs thing -> c (HsWildCardBndrs GhcPs thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcPs thing) # toConstr :: HsWildCardBndrs GhcPs thing -> Constr # dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcPs thing -> HsWildCardBndrs GhcPs thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) # | |
Data flag => Data (HsOuterTyVarBndrs flag GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcTc -> c (HsOuterTyVarBndrs flag GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcTc) # toConstr :: HsOuterTyVarBndrs flag GhcTc -> Constr # dataTypeOf :: HsOuterTyVarBndrs flag GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcTc -> HsOuterTyVarBndrs flag GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) # | |
Data flag => Data (HsOuterTyVarBndrs flag GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcRn -> c (HsOuterTyVarBndrs flag GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcRn) # toConstr :: HsOuterTyVarBndrs flag GhcRn -> Constr # dataTypeOf :: HsOuterTyVarBndrs flag GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcRn -> HsOuterTyVarBndrs flag GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) # | |
Data flag => Data (HsOuterTyVarBndrs flag GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcPs -> c (HsOuterTyVarBndrs flag GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcPs) # toConstr :: HsOuterTyVarBndrs flag GhcPs -> Constr # dataTypeOf :: HsOuterTyVarBndrs flag GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcPs -> HsOuterTyVarBndrs flag GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) # | |
Data body => Data (HsRecFields GhcTc body) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcTc body -> c (HsRecFields GhcTc body) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcTc body) # toConstr :: HsRecFields GhcTc body -> Constr # dataTypeOf :: HsRecFields GhcTc body -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcTc body)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcTc body)) # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcTc body -> HsRecFields GhcTc body # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) # | |
Data body => Data (HsRecFields GhcRn body) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcRn body -> c (HsRecFields GhcRn body) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcRn body) # toConstr :: HsRecFields GhcRn body -> Constr # dataTypeOf :: HsRecFields GhcRn body -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcRn body)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcRn body)) # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcRn body -> HsRecFields GhcRn body # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) # | |
Data body => Data (HsRecFields GhcPs body) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcPs body -> c (HsRecFields GhcPs body) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcPs body) # toConstr :: HsRecFields GhcPs body -> Constr # dataTypeOf :: HsRecFields GhcPs body -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcPs body)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcPs body)) # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcPs body -> HsRecFields GhcPs body # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) # | |
Data (PatSynBind GhcTc GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcTc GhcTc -> c (PatSynBind GhcTc GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcTc GhcTc) # toConstr :: PatSynBind GhcTc GhcTc -> Constr # dataTypeOf :: PatSynBind GhcTc GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcTc GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcTc GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcTc GhcTc -> PatSynBind GhcTc GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) # | |
Data (PatSynBind GhcRn GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcRn GhcRn -> c (PatSynBind GhcRn GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcRn GhcRn) # toConstr :: PatSynBind GhcRn GhcRn -> Constr # dataTypeOf :: PatSynBind GhcRn GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcRn GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcRn GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcRn GhcRn -> PatSynBind GhcRn GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) # | |
Data (PatSynBind GhcPs GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcPs GhcRn -> c (PatSynBind GhcPs GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcRn) # toConstr :: PatSynBind GhcPs GhcRn -> Constr # dataTypeOf :: PatSynBind GhcPs GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcRn -> PatSynBind GhcPs GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) # | |
Data (PatSynBind GhcPs GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcPs GhcPs -> c (PatSynBind GhcPs GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcPs) # toConstr :: PatSynBind GhcPs GhcPs -> Constr # dataTypeOf :: PatSynBind GhcPs GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcPs -> PatSynBind GhcPs GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) # | |
Data (HsBindLR GhcTc GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcTc GhcTc -> c (HsBindLR GhcTc GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcTc GhcTc) # toConstr :: HsBindLR GhcTc GhcTc -> Constr # dataTypeOf :: HsBindLR GhcTc GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcTc GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcTc GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcTc GhcTc -> HsBindLR GhcTc GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) # | |
Data (HsBindLR GhcRn GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcRn GhcRn -> c (HsBindLR GhcRn GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcRn GhcRn) # toConstr :: HsBindLR GhcRn GhcRn -> Constr # dataTypeOf :: HsBindLR GhcRn GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcRn GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcRn GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcRn GhcRn -> HsBindLR GhcRn GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) # | |
Data (HsBindLR GhcPs GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcPs GhcRn -> c (HsBindLR GhcPs GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcRn) # toConstr :: HsBindLR GhcPs GhcRn -> Constr # dataTypeOf :: HsBindLR GhcPs GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcRn -> HsBindLR GhcPs GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) # | |
Data (HsBindLR GhcPs GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcPs GhcPs -> c (HsBindLR GhcPs GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcPs) # toConstr :: HsBindLR GhcPs GhcPs -> Constr # dataTypeOf :: HsBindLR GhcPs GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcPs -> HsBindLR GhcPs GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) # | |
Data (HsValBindsLR GhcTc GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcTc GhcTc -> c (HsValBindsLR GhcTc GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcTc GhcTc) # toConstr :: HsValBindsLR GhcTc GhcTc -> Constr # dataTypeOf :: HsValBindsLR GhcTc GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcTc GhcTc -> HsValBindsLR GhcTc GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) # | |
Data (HsValBindsLR GhcRn GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcRn GhcRn -> c (HsValBindsLR GhcRn GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcRn GhcRn) # toConstr :: HsValBindsLR GhcRn GhcRn -> Constr # dataTypeOf :: HsValBindsLR GhcRn GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcRn GhcRn -> HsValBindsLR GhcRn GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) # | |
Data (HsValBindsLR GhcPs GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcPs GhcRn -> c (HsValBindsLR GhcPs GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcRn) # toConstr :: HsValBindsLR GhcPs GhcRn -> Constr # dataTypeOf :: HsValBindsLR GhcPs GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcRn -> HsValBindsLR GhcPs GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) # | |
Data (HsValBindsLR GhcPs GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcPs GhcPs -> c (HsValBindsLR GhcPs GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcPs) # toConstr :: HsValBindsLR GhcPs GhcPs -> Constr # dataTypeOf :: HsValBindsLR GhcPs GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcPs -> HsValBindsLR GhcPs GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) # | |
Data (HsLocalBindsLR GhcTc GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcTc GhcTc -> c (HsLocalBindsLR GhcTc GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcTc GhcTc) # toConstr :: HsLocalBindsLR GhcTc GhcTc -> Constr # dataTypeOf :: HsLocalBindsLR GhcTc GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcTc GhcTc -> HsLocalBindsLR GhcTc GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) # | |
Data (HsLocalBindsLR GhcRn GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcRn GhcRn -> c (HsLocalBindsLR GhcRn GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcRn GhcRn) # toConstr :: HsLocalBindsLR GhcRn GhcRn -> Constr # dataTypeOf :: HsLocalBindsLR GhcRn GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcRn GhcRn -> HsLocalBindsLR GhcRn GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) # | |
Data (HsLocalBindsLR GhcPs GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcPs GhcRn -> c (HsLocalBindsLR GhcPs GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcRn) # toConstr :: HsLocalBindsLR GhcPs GhcRn -> Constr # dataTypeOf :: HsLocalBindsLR GhcPs GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcRn -> HsLocalBindsLR GhcPs GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) # | |
Data (HsLocalBindsLR GhcPs GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcPs GhcPs -> c (HsLocalBindsLR GhcPs GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcPs) # toConstr :: HsLocalBindsLR GhcPs GhcPs -> Constr # dataTypeOf :: HsLocalBindsLR GhcPs GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcPs -> HsLocalBindsLR GhcPs GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) # | |
Data rhs => Data (FamEqn GhcTc rhs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamEqn GhcTc rhs -> c (FamEqn GhcTc rhs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcTc rhs) # toConstr :: FamEqn GhcTc rhs -> Constr # dataTypeOf :: FamEqn GhcTc rhs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcTc rhs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcTc rhs)) # gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcTc rhs -> FamEqn GhcTc rhs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcTc rhs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcTc rhs -> r # gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcTc rhs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcTc rhs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) # | |
Data rhs => Data (FamEqn GhcRn rhs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamEqn GhcRn rhs -> c (FamEqn GhcRn rhs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcRn rhs) # toConstr :: FamEqn GhcRn rhs -> Constr # dataTypeOf :: FamEqn GhcRn rhs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcRn rhs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcRn rhs)) # gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcRn rhs -> FamEqn GhcRn rhs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcRn rhs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcRn rhs -> r # gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcRn rhs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcRn rhs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) # | |
Data rhs => Data (FamEqn GhcPs rhs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamEqn GhcPs rhs -> c (FamEqn GhcPs rhs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcPs rhs) # toConstr :: FamEqn GhcPs rhs -> Constr # dataTypeOf :: FamEqn GhcPs rhs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcPs rhs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcPs rhs)) # gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcPs rhs -> FamEqn GhcPs rhs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcPs rhs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcPs rhs -> r # gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcPs rhs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcPs rhs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) # | |
Data (ParStmtBlock GhcTc GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcTc GhcTc -> c (ParStmtBlock GhcTc GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcTc GhcTc) # toConstr :: ParStmtBlock GhcTc GhcTc -> Constr # dataTypeOf :: ParStmtBlock GhcTc GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcTc GhcTc -> ParStmtBlock GhcTc GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) # | |
Data (ParStmtBlock GhcRn GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcRn GhcRn -> c (ParStmtBlock GhcRn GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcRn GhcRn) # toConstr :: ParStmtBlock GhcRn GhcRn -> Constr # dataTypeOf :: ParStmtBlock GhcRn GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcRn GhcRn -> ParStmtBlock GhcRn GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) # | |
Data (ParStmtBlock GhcPs GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcPs GhcRn -> c (ParStmtBlock GhcPs GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcRn) # toConstr :: ParStmtBlock GhcPs GhcRn -> Constr # dataTypeOf :: ParStmtBlock GhcPs GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcRn -> ParStmtBlock GhcPs GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) # | |
Data (ParStmtBlock GhcPs GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcPs GhcPs -> c (ParStmtBlock GhcPs GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcPs) # toConstr :: ParStmtBlock GhcPs GhcPs -> Constr # dataTypeOf :: ParStmtBlock GhcPs GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcPs -> ParStmtBlock GhcPs GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) # | |
Data (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) # toConstr :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> Constr # dataTypeOf :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) # | |
Data (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) # toConstr :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> Constr # dataTypeOf :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) # | |
Data (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) # toConstr :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> Constr # dataTypeOf :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) # | |
Data (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) # toConstr :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> Constr # dataTypeOf :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) # | |
Data (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) # toConstr :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> Constr # dataTypeOf :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) # | |
Data (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) # toConstr :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> Constr # dataTypeOf :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) # | |
Data (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) # toConstr :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> Constr # dataTypeOf :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> Match GhcTc (LocatedA (HsExpr GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) # | |
Data (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) # toConstr :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> Constr # dataTypeOf :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> Match GhcTc (LocatedA (HsCmd GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) # | |
Data (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) # toConstr :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> Constr # dataTypeOf :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> Match GhcRn (LocatedA (HsExpr GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) # | |
Data (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) # toConstr :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> Constr # dataTypeOf :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> Match GhcRn (LocatedA (HsCmd GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) # | |
Data (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) # toConstr :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> Constr # dataTypeOf :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> Match GhcPs (LocatedA (HsExpr GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) # | |
Data (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) # toConstr :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> Constr # dataTypeOf :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> Match GhcPs (LocatedA (HsCmd GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) # | |
(OutputableBndrId p, OutputableBndrFlag flag p) => Outputable (HsTyVarBndr flag (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) Source # | |
Defined in GHC.Hs.Type | |
(OutputableBndrFlag flag p, OutputableBndrFlag flag (NoGhcTcPass p), OutputableBndrId p) => Outputable (HsOuterTyVarBndrs flag (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
(OutputableBndrId l, OutputableBndrId r) => Outputable (PatSynBind (GhcPass l) (GhcPass r)) Source # | |
Defined in GHC.Hs.Binds | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsBindLR (GhcPass pl) (GhcPass pr)) Source # | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsValBindsLR (GhcPass pl) (GhcPass pr)) Source # | |
Defined in GHC.Hs.Binds | |
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsLocalBindsLR (GhcPass pl) (GhcPass pr)) Source # | |
Defined in GHC.Hs.Binds | |
(Outputable (StmtLR (GhcPass idL) (GhcPass idL) (LHsExpr (GhcPass idL))), Outputable (XXParStmtBlock (GhcPass idL) (GhcPass idR))) => Outputable (ParStmtBlock (GhcPass idL) (GhcPass idR)) Source # | |
Defined in GHC.Hs.Expr | |
(OutputableBndrId pr, Outputable body) => Outputable (Match (GhcPass pr) body) Source # | |
NamedThing (HsTyVarBndr flag GhcRn) Source # | |
Defined in GHC.Hs.Type getOccName :: HsTyVarBndr flag GhcRn -> OccName Source # | |
Data (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) # toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> Constr # dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) # | |
Data (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) # toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> Constr # dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) # | |
Data (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) # toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> Constr # dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) # | |
Data (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) # toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> Constr # dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) # | |
Data (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) # toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr # dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) # | |
Data (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) # toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr # dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) # | |
Data (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) # toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr # dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) # | |
Data (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) # toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr # dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) # | |
(OutputableBndrId pl, OutputableBndrId pr, Anno (StmtLR (GhcPass pl) (GhcPass pr) body) ~ SrcSpanAnnA, Outputable body) => Outputable (StmtLR (GhcPass pl) (GhcPass pr) body) Source # | |
type XIEModuleContents GhcTc Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEModuleContents GhcRn Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEModuleContents GhcPs Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEVar GhcTc Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEVar GhcRn Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEVar GhcPs Source # | |
Defined in GHC.Hs.ImpExp | |
type XCImportDecl GhcTc Source # | |
Defined in GHC.Hs.ImpExp | |
type XCImportDecl GhcRn Source # | |
Defined in GHC.Hs.ImpExp | |
type XCImportDecl GhcPs Source # | |
Defined in GHC.Hs.ImpExp | |
type XCFieldOcc GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XCFieldOcc GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XCFieldOcc GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XExplicitTupleTy GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XExplicitTupleTy GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XExplicitTupleTy GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XExplicitListTy GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XExplicitListTy GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XExplicitListTy GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XRecTy GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XRecTy GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XRecTy GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XSpliceTy GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XSpliceTy GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XSpliceTy GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XHsPS GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XHsPS GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XHsPS GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XHsOuterImplicit GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XHsOuterImplicit GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XHsOuterImplicit GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XHsQTvs GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XHsQTvs GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XHsQTvs GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XXPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XXPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XXPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XSigPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XSigPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XSigPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XNPlusKPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XNPlusKPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XNPlusKPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XNPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XNPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XNPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XViewPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XViewPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XViewPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XConPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XConPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XConPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XSumPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XSumPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XSumPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XTuplePat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XTuplePat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XTuplePat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XListPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XListPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XListPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XBangPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XBangPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XBangPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XAsPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XAsPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XAsPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XLazyPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XLazyPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XLazyPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XWildPat GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type XWildPat GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type XWildPat GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XOverLit GhcTc Source # | |
Defined in GHC.Hs.Lit | |
type XOverLit GhcRn Source # | |
Defined in GHC.Hs.Lit | |
type XOverLit GhcPs Source # | |
Defined in GHC.Hs.Lit | |
type XApplicativeArgOne GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XApplicativeArgOne GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XApplicativeArgOne GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XXCmd GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XXCmd GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XXCmd GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCmdDo GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XCmdDo GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XCmdDo GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCmdLet GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XCmdLet GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XCmdLet GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCmdIf GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XCmdIf GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XCmdIf GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCmdCase GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XCmdCase GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XCmdCase GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCmdArrForm GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XCmdArrForm GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XCmdArrForm GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCmdArrApp GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XCmdArrApp GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XCmdArrApp GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCmdTop GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XCmdTop GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XCmdTop GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XXSplice GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XXSplice GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XXSplice GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XMissing GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XMissing GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XMissing GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XAmbiguous GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XAmbiguous GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XAmbiguous GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XUnambiguous GhcTc Source # | |
Defined in GHC.Hs.Type | |
type XUnambiguous GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XUnambiguous GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XXExpr GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XXExpr GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XXExpr GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XStatic GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XStatic GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XStatic GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XArithSeq GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XArithSeq GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XArithSeq GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XExprWithTySig GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XExprWithTySig GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XExprWithTySig GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XProjection GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XProjection GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XProjection GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XGetField GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XGetField GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XGetField GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XRecordUpd GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XRecordUpd GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XRecordUpd GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XRecordCon GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XRecordCon GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XRecordCon GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitList GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitList GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitList GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XDo GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XDo GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XDo GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XLet GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XLet GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XLet GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XMultiIf GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XMultiIf GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XMultiIf GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XIf GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XIf GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XIf GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCase GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XCase GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XCase GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitSum GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitSum GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitSum GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitTuple GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitTuple GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XExplicitTuple GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XSectionR GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XSectionR GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XSectionR GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XSectionL GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XSectionL GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XSectionL GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XNegApp GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XNegApp GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XNegApp GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XOpApp GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XOpApp GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XOpApp GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XAppTypeE GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XAppTypeE GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XAppTypeE GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XOverLabel GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XOverLabel GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XOverLabel GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XUnboundVar GhcTc Source # | |
Defined in GHC.Hs.Expr | |
type XUnboundVar GhcRn Source # | |
Defined in GHC.Hs.Expr | |
type XUnboundVar GhcPs Source # | |
Defined in GHC.Hs.Expr | |
type XCRoleAnnotDecl GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XCRoleAnnotDecl GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XCRoleAnnotDecl GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XWarnings GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XWarnings GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XWarnings GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XHsRule GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XHsRule GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XHsRule GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XCRuleDecls GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XCRuleDecls GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XCRuleDecls GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XForeignExport GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XForeignExport GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XForeignExport GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XForeignImport GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XForeignImport GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XForeignImport GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XCDefaultDecl GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XCDefaultDecl GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XCDefaultDecl GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XViaStrategy GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XViaStrategy GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XViaStrategy GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XNewtypeStrategy GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XNewtypeStrategy GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XNewtypeStrategy GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XAnyClassStrategy GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XAnyClassStrategy GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XAnyClassStrategy GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XStockStrategy GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XStockStrategy GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XStockStrategy GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XTyFamInstD GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XTyFamInstD GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XTyFamInstD GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XDataFamInstD GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XDataFamInstD GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XDataFamInstD GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XCClsInstDecl GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XCClsInstDecl GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XCClsInstDecl GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XClassDecl GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XClassDecl GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XClassDecl GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XDataDecl GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XDataDecl GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XDataDecl GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XSynDecl GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XSynDecl GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XSynDecl GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XStandaloneKindSig GhcTc Source # | |
Defined in GHC.Hs.Decls | |
type XStandaloneKindSig GhcRn Source # | |
Defined in GHC.Hs.Decls | |
type XStandaloneKindSig GhcPs Source # | |
Defined in GHC.Hs.Decls | |
type XIPBinds GhcTc Source # | |
Defined in GHC.Hs.Binds | |
type XIPBinds GhcRn Source # | |
Defined in GHC.Hs.Binds | |
type XIPBinds GhcPs Source # | |
Defined in GHC.Hs.Binds | |
type ConLikeP GhcTc Source # | |
Defined in GHC.Hs.Pat | |
type ConLikeP GhcRn Source # | |
Defined in GHC.Hs.Pat | |
type ConLikeP GhcPs Source # | |
Defined in GHC.Hs.Pat | |
type XHsWC GhcTc b Source # | |
Defined in GHC.Hs.Type | |
type XHsWC GhcRn b Source # | |
Defined in GHC.Hs.Type | |
type XHsWC GhcPs b Source # | |
Defined in GHC.Hs.Type | |
type XHsOuterExplicit GhcTc flag Source # | |
Defined in GHC.Hs.Type | |
type XHsOuterExplicit GhcRn _1 Source # | |
Defined in GHC.Hs.Type | |
type XHsOuterExplicit GhcPs _1 Source # | |
Defined in GHC.Hs.Type | |
type XMG GhcTc b Source # | |
Defined in GHC.Hs.Expr | |
type XMG GhcRn b Source # | |
Defined in GHC.Hs.Expr | |
type XMG GhcPs b Source # | |
Defined in GHC.Hs.Expr | |
type XPatBind GhcTc (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XPatBind GhcRn (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XPatBind GhcPs (GhcPass pR) Source # | |
type NoGhcTc (GhcPass pass) Source # | Marks that a field uses the GhcRn variant even when the pass parameter is GhcTc. Useful for storing HsTypes in GHC.Hs.Exprs, say, because HsType GhcTc should never occur. See Note [NoGhcTc] |
Defined in GHC.Hs.Extension | |
type XXIE (GhcPass _1) Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEDocNamed (GhcPass _1) Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEDoc (GhcPass _1) Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEGroup (GhcPass _1) Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEThingWith (GhcPass 'Parsed) Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEThingWith (GhcPass 'Renamed) Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEThingWith (GhcPass 'Typechecked) Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEThingAll (GhcPass _1) Source # | |
Defined in GHC.Hs.ImpExp | |
type XIEThingAbs (GhcPass _1) Source # | |
Defined in GHC.Hs.ImpExp | |
type XXImportDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.ImpExp | |
type XXFieldOcc (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXConDeclField (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XConDeclField (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXTyVarBndr (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XKindedTyVar (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XUserTyVar (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXHsForAllTelescope (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XHsForAllInvis (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XHsForAllVis (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXType (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XWildCardTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XTyLit (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XBangTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XDocTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XKindSig (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XStarTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XIParamTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XParTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XOpTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XSumTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XTupleTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XListTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XFunTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XAppKindTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XAppTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XTyVar (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XQualTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XForAllTy (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXHsPatSigType (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXHsSigType (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XHsSig (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXHsOuterTyVarBndrs (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXLHsQTyVars (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XLitPat (GhcPass _1) Source # | |
Defined in GHC.Hs.Pat | |
type XSplicePat (GhcPass _1) Source # | |
Defined in GHC.Hs.Pat | |
type XParPat (GhcPass _1) Source # | |
Defined in GHC.Hs.Pat | |
type XVarPat (GhcPass _1) Source # | |
Defined in GHC.Hs.Pat | |
type XXOverLit (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XXLit (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsDoublePrim (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsFloatPrim (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsRat (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsInteger (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsWord64Prim (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsInt64Prim (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsWordPrim (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsIntPrim (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsInt (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsStringPrim (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsString (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsCharPrim (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XHsChar (GhcPass _1) Source # | |
Defined in GHC.Hs.Lit | |
type XXApplicativeArg (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XApplicativeArgMany (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XCmdWrap (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XCmdLamCase (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XCmdPar (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XCmdLam (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XCmdApp (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XXCmdTop (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XXBracket (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XTExpBr (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XVarBr (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XTypBr (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XDecBrG (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XDecBrL (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XPatBr (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XExpBr (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XSpliced (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XQuasiQuote (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XUntypedSplice (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XTypedSplice (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XXTupArg (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XPresent (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XXAmbiguousFieldOcc (GhcPass _1) Source # | |
Defined in GHC.Hs.Type | |
type XXPragE (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XSCC (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XXHsFieldLabel (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XCHsFieldLabel (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XPragE (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XBinTick (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XTick (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XProc (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XSpliceE (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XTcBracketOut (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XRnBracketOut (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XBracket (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XPar (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XApp (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XLamCase (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XLam (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XLam (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XLitE (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XOverLitE (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XIPVar (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XRecFld (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XRecFld (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XConLikeOut (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XConLikeOut (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XVar (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XVar (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type XXInjectivityAnn (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCInjectivityAnn (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXRoleAnnotDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXAnnDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XHsAnnotation (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXWarnDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XWarning (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXWarnDecls (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXRuleBndr (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XRuleBndrSig (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCRuleBndr (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXRuleDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXRuleDecls (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXForeignDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXDefaultDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXDerivDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCDerivDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXInstDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XClsInstD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXClsInstDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXTyFamInstDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCTyFamInstDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXConDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XConDeclH98 (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XConDeclGADT (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXDerivClauseTys (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XDctMulti (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XDctSingle (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXHsDerivingClause (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCHsDerivingClause (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXHsDataDefn (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCHsDataDefn (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXFamilyDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCFamilyDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXFamilyResultSig (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XTyVarSig (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCKindSig (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XNoSig (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXTyClGroup (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCTyClGroup (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXFunDep (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCFunDep (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXTyClDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XFamDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXSpliceDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XSpliceDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXHsGroup (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XCHsGroup (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXHsDecl (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XRoleAnnotD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XDocD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XSpliceD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XRuleD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XAnnD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XWarningD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XForD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XDefD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XKindSigD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XSigD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XValD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XDerivD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XInstD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XTyClD (GhcPass _1) Source # | |
Defined in GHC.Hs.Decls | |
type XXStandaloneKindSig (GhcPass p) Source # | |
Defined in GHC.Hs.Decls | |
type XXFixitySig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XFixitySig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XXSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XCompleteMatchSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XSCCFunSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XMinimalSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XSpecInstSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XSpecSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XInlineSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XFixSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XIdSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XClassOpSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XPatSynSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XTypeSig (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XXIPBind (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XCIPBind (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XXHsIPBinds (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XXABExport (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type XABE (GhcPass p) Source # | |
Defined in GHC.Hs.Binds | |
type IdP (GhcPass p) Source # | |
Defined in GHC.Hs.Extension | |
type Anno [LocatedA (IE (GhcPass p))] Source # | |
Defined in GHC.Hs.ImpExp | |
type Anno [LocatedA (ConDeclField (GhcPass _1))] Source # | |
Defined in GHC.Hs.Decls | |
type Anno [LocatedA (HsType (GhcPass p))] Source # | |
Defined in GHC.Hs.Type | |
type Anno [LocatedA (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] Source # | |
Defined in GHC.Parser.Types | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] Source # | |
Defined in GHC.Parser.PostProcess | |
type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] Source # | |
Defined in GHC.Hs.Expr | |
type Anno (LocatedA (IE (GhcPass p))) Source # | |
Defined in GHC.Hs.ImpExp | |
type Anno (HsSplice (GhcPass p)) Source # | |
Defined in GHC.Hs.Expr | |
type Anno (HsExpr (GhcPass p)) Source # | |
Defined in GHC.Hs.Expr | |
type Anno (IE (GhcPass p)) Source # | |
Defined in GHC.Hs.ImpExp | |
type Anno (ImportDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.ImpExp | |
type Anno (HsOverLit (GhcPass p)) Source # | |
Defined in GHC.Hs.Pat | |
type Anno (Pat (GhcPass p)) Source # | |
Defined in GHC.Hs.Pat | |
type Anno (AmbiguousFieldOcc GhcTc) Source # | |
Defined in GHC.Hs.Pat | |
type Anno (FieldOcc (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (ConDeclField (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsType (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsSigType (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsKind (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (BangType (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (FixitySig (GhcPass p)) Source # | |
Defined in GHC.Hs.Binds | |
type Anno (Sig (GhcPass p)) Source # | |
Defined in GHC.Hs.Binds | |
type Anno (IPBind (GhcPass p)) Source # | |
Defined in GHC.Hs.Binds | |
type Anno (RoleAnnotDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (AnnDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (WarnDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (WarnDecls (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (RuleBndr (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (RuleDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (RuleDecls (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (ForeignDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (DefaultDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (DerivStrategy (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (DerivDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (InstDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (ClsInstDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (DataFamInstDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (TyFamInstDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (ConDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (StandaloneKindSig (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (DerivClauseTys (GhcPass _1)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (HsDerivingClause (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (InjectivityAnn (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (FamilyDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (FamilyResultSig (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (FunDep (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (TyClDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (SpliceDecl (GhcPass p)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (HsDecl (GhcPass _1)) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (HsCmdTop (GhcPass p)) Source # | |
Defined in GHC.Hs.Expr | |
type Anno (HsCmd (GhcPass p)) Source # | |
Defined in GHC.Hs.Expr | |
type SyntaxExpr (GhcPass p) Source # | |
Defined in GHC.Hs.Expr | |
type PendingTcSplice' (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type PendingRnSplice' (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type HsBracketRn (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type HsDoRn (GhcPass _1) Source # | |
Defined in GHC.Hs.Expr | |
type Body (HsExpr GhcPs) Source # | |
Defined in GHC.Parser.PostProcess | |
type Body (HsCmd GhcPs) Source # | |
Defined in GHC.Parser.PostProcess | |
type Body (PatBuilder GhcPs) Source # | |
Defined in GHC.Parser.PostProcess | |
type InfixOp (HsExpr GhcPs) Source # | |
type InfixOp (HsCmd GhcPs) Source # | |
type InfixOp (PatBuilder GhcPs) Source # | |
Defined in GHC.Parser.PostProcess | |
type FunArg (HsExpr GhcPs) Source # | |
type FunArg (HsCmd GhcPs) Source # | |
type FunArg (PatBuilder GhcPs) Source # | |
Defined in GHC.Parser.PostProcess | |
type XXHsWildCardBndrs (GhcPass _1) _2 Source # | |
Defined in GHC.Hs.Type | |
type XXGRHS (GhcPass _1) b Source # | |
Defined in GHC.Hs.Expr | |
type XCGRHS (GhcPass _1) _2 Source # | |
Defined in GHC.Hs.Expr | |
type XXGRHSs (GhcPass _1) _2 Source # | |
Defined in GHC.Hs.Expr | |
type XCGRHSs (GhcPass _1) _2 Source # | |
Defined in GHC.Hs.Expr | |
type XXMatch (GhcPass _1) b Source # | |
Defined in GHC.Hs.Expr | |
type XCMatch (GhcPass _1) b Source # | |
Defined in GHC.Hs.Expr | |
type XXMatchGroup (GhcPass _1) b Source # | |
Defined in GHC.Hs.Expr | |
type XXFamEqn (GhcPass _1) r Source # | |
Defined in GHC.Hs.Decls | |
type XCFamEqn (GhcPass _1) r Source # | |
Defined in GHC.Hs.Decls | |
type XPSB (GhcPass idL) GhcTc Source # | |
Defined in GHC.Hs.Binds | |
type XPSB (GhcPass idL) GhcRn Source # | |
Defined in GHC.Hs.Binds | |
type XPSB (GhcPass idL) GhcPs Source # | |
type XFunBind (GhcPass pL) GhcTc Source # | |
Defined in GHC.Hs.Binds | |
type XFunBind (GhcPass pL) GhcRn Source # | |
Defined in GHC.Hs.Binds | |
type XFunBind (GhcPass pL) GhcPs Source # | |
Defined in GHC.Hs.Binds | |
type XRec (GhcPass p) a Source # | |
Defined in GHC.Hs.Extension | |
type XRecStmt (GhcPass _1) GhcRn b Source # | |
Defined in GHC.Hs.Expr | |
type XRecStmt (GhcPass _1) GhcPs b Source # | |
type XRecStmt (GhcPass _1) GhcTc b Source # | |
Defined in GHC.Hs.Expr | |
type XTransStmt (GhcPass _1) GhcTc b Source # | |
Defined in GHC.Hs.Expr | |
type XTransStmt (GhcPass _1) GhcRn b Source # | |
Defined in GHC.Hs.Expr | |
type XTransStmt (GhcPass _1) GhcPs b Source # | |
Defined in GHC.Hs.Expr | |
type XParStmt (GhcPass _1) GhcTc b Source # | |
Defined in GHC.Hs.Expr | |
type XParStmt (GhcPass _1) GhcRn b Source # | |
Defined in GHC.Hs.Expr | |
type XParStmt (GhcPass _1) GhcPs b Source # | |
Defined in GHC.Hs.Expr | |
type XBodyStmt (GhcPass _1) GhcTc b Source # | |
Defined in GHC.Hs.Expr | |
type XBodyStmt (GhcPass _1) GhcRn b Source # | |
Defined in GHC.Hs.Expr | |
type XBodyStmt (GhcPass _1) GhcPs b Source # | |
Defined in GHC.Hs.Expr | |
type XApplicativeStmt (GhcPass _1) GhcTc b Source # | |
Defined in GHC.Hs.Expr | |
type XApplicativeStmt (GhcPass _1) GhcRn b Source # | |
Defined in GHC.Hs.Expr | |
type XApplicativeStmt (GhcPass _1) GhcPs b Source # | |
Defined in GHC.Hs.Expr | |
type XBindStmt (GhcPass _1) GhcPs b Source # | |
type XBindStmt (GhcPass _1) GhcRn b Source # | |
Defined in GHC.Hs.Expr | |
type XBindStmt (GhcPass _1) GhcTc b Source # | |
Defined in GHC.Hs.Expr | |
type XXParStmtBlock (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Expr | |
type XParStmtBlock (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Expr | |
type XXPatSynBind (GhcPass idL) (GhcPass idR) Source # | |
Defined in GHC.Hs.Binds | |
type XXHsBindsLR (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XPatSynBind (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XAbsBinds (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XVarBind (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XXValBindsLR (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XValBinds (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XHsIPBinds (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XHsValBinds (GhcPass pL) (GhcPass pR) Source # | |
Defined in GHC.Hs.Binds | |
type XXStmtLR (GhcPass _1) (GhcPass _2) b Source # | |
Defined in GHC.Hs.Expr | |
type XLetStmt (GhcPass _1) (GhcPass _2) b Source # | |
type XLastStmt (GhcPass _1) (GhcPass _2) b Source # | |
Defined in GHC.Hs.Expr | |
type Anno (HsTyVarBndr _flag GhcTc) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag GhcRn) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag GhcPs) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag (GhcPass _1)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsRecField' (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # | |
Defined in GHC.Hs.Pat | |
type Anno (HsRecField (GhcPass p) arg) Source # | |
Defined in GHC.Hs.Pat | |
type Anno (HsBindLR (GhcPass idL) (GhcPass idR)) Source # | |
Defined in GHC.Hs.Binds | |
type Anno (FamEqn (GhcPass p) _1) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (FamEqn (GhcPass p) _1) Source # | |
Defined in GHC.Hs.Decls | |
type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) Source # | |
Defined in GHC.Parser.PostProcess | |
type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # | |
type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # | |
type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) Source # | |
Defined in GHC.Parser.PostProcess | |
type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # | |
Defined in GHC.Hs.Expr | |
type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # | |
Defined in GHC.Hs.Expr | |
type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) Source # | |
Defined in GHC.Hs.Expr | |
type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) Source # | |
Defined in GHC.Parser.PostProcess | |
type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr)))) Source # | |
Defined in GHC.Hs.Expr | |
type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr)))) Source # | |
Defined in GHC.Hs.Expr |
Instances
Data Pass Source # | |
Defined in GHC.Hs.Extension gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pass -> c Pass # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pass # dataTypeOf :: Pass -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pass) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass) # gmapT :: (forall b. Data b => b -> b) -> Pass -> Pass # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r # gmapQ :: (forall d. Data d => d -> u) -> Pass -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pass -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pass -> m Pass # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass # |
type GhcTc = GhcPass 'Typechecked Source #
class (NoGhcTcPass (NoGhcTcPass p) ~ NoGhcTcPass p, IsPass (NoGhcTcPass p)) => IsPass p where Source #
Allows us to check what phase we're in at GHC's runtime. For example, this class allows us to write > f :: forall p. IsPass p => HsExpr (GhcPass p) -> blah > f e = case ghcPass @p of > GhcPs -> ... in this RHS we have HsExpr GhcPs... > GhcRn -> ... in this RHS we have HsExpr GhcRn... > GhcTc -> ... in this RHS we have HsExpr GhcTc... which is very useful, for example, when pretty-printing. See Note [IsPass].
type family NoGhcTcPass (p :: Pass) :: Pass where ... Source #
NoGhcTcPass 'Typechecked = 'Renamed | |
NoGhcTcPass other = other |
type OutputableBndrId pass = (OutputableBndr (IdGhcP pass), OutputableBndr (IdGhcP (NoGhcTcPass pass)), Outputable (GenLocated (Anno (IdGhcP pass)) (IdGhcP pass)), Outputable (GenLocated (Anno (IdGhcP (NoGhcTcPass pass))) (IdGhcP (NoGhcTcPass pass))), IsPass pass) Source #
Constraint type to bundle up the requirement for OutputableBndr
on both
the id
and the NoGhcTc
of it. See Note [NoGhcTc].