Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type IsSrcSpanAnn (p :: Pass) 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 :: Pass) where
- type family IdGhcP (pass :: Pass) where ...
- type family NoGhcTcPass (p :: Pass) :: Pass where ...
- type OutputableBndrId (pass :: 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 :: Pass). IsPass p => (p ~ 'Parsed => SDoc) -> SDoc
- pprIfRn :: forall (p :: Pass). IsPass p => (p ~ 'Renamed => SDoc) -> SDoc
- pprIfTc :: forall (p :: Pass). IsPass p => (p ~ 'Typechecked => SDoc) -> SDoc
- noHsTok :: forall (tok :: Symbol). GenLocated TokenLocation (HsToken tok)
- noHsUniTok :: forall (tok :: Symbol) (utok :: Symbol). GenLocated TokenLocation (HsUniToken tok utok)
Documentation
type IsSrcSpanAnn (p :: Pass) 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
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcPs) Source # toConstr :: NHsValBindsLR GhcPs -> Constr Source # dataTypeOf :: NHsValBindsLR GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcPs -> NHsValBindsLR GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcPs -> m (NHsValBindsLR GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcRn) Source # toConstr :: NHsValBindsLR GhcRn -> Constr Source # dataTypeOf :: NHsValBindsLR GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcRn -> NHsValBindsLR GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcRn -> m (NHsValBindsLR GhcRn) Source # | |||||||||||||
Data (NHsValBindsLR 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NHsValBindsLR GhcTc) Source # toConstr :: NHsValBindsLR GhcTc -> Constr Source # dataTypeOf :: NHsValBindsLR GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NHsValBindsLR GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NHsValBindsLR GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> NHsValBindsLR GhcTc -> NHsValBindsLR GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NHsValBindsLR GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> NHsValBindsLR GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> NHsValBindsLR GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NHsValBindsLR GhcTc -> m (NHsValBindsLR GhcTc) Source # | |||||||||||||
Data (HsRecUpdParent GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecUpdParent GhcPs -> c (HsRecUpdParent GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecUpdParent GhcPs) Source # toConstr :: HsRecUpdParent GhcPs -> Constr Source # dataTypeOf :: HsRecUpdParent GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecUpdParent GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecUpdParent GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecUpdParent GhcPs -> HsRecUpdParent GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecUpdParent GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecUpdParent GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcPs -> m (HsRecUpdParent GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcPs -> m (HsRecUpdParent GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcPs -> m (HsRecUpdParent GhcPs) Source # | |||||||||||||
Data (HsRecUpdParent GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecUpdParent GhcRn -> c (HsRecUpdParent GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecUpdParent GhcRn) Source # toConstr :: HsRecUpdParent GhcRn -> Constr Source # dataTypeOf :: HsRecUpdParent GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecUpdParent GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecUpdParent GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecUpdParent GhcRn -> HsRecUpdParent GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecUpdParent GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecUpdParent GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcRn -> m (HsRecUpdParent GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcRn -> m (HsRecUpdParent GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcRn -> m (HsRecUpdParent GhcRn) Source # | |||||||||||||
Data (HsRecUpdParent GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecUpdParent GhcTc -> c (HsRecUpdParent GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecUpdParent GhcTc) Source # toConstr :: HsRecUpdParent GhcTc -> Constr Source # dataTypeOf :: HsRecUpdParent GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecUpdParent GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecUpdParent GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecUpdParent GhcTc -> HsRecUpdParent GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecUpdParent GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecUpdParent GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecUpdParent GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcTc -> m (HsRecUpdParent GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcTc -> m (HsRecUpdParent GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecUpdParent GhcTc -> m (HsRecUpdParent GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GhcPass p) Source # toConstr :: GhcPass p -> Constr Source # dataTypeOf :: GhcPass p -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GhcPass p)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GhcPass p)) Source # gmapT :: (forall b. Data b => b -> b) -> GhcPass p -> GhcPass p Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GhcPass p -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GhcPass p -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GhcPass p -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GhcPass p -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GhcPass p -> m (GhcPass p) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GhcPass p -> m (GhcPass p) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GhcPass p -> m (GhcPass p) Source # | |||||||||||||
Data (HsModule GhcPs) Source # | |||||||||||||
Defined in GHC.Hs gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcPs -> c (HsModule GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcPs) Source # toConstr :: HsModule GhcPs -> Constr Source # dataTypeOf :: HsModule GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsModule GhcPs -> HsModule GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcPs) Source # toConstr :: FixitySig GhcPs -> Constr Source # dataTypeOf :: FixitySig GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcPs -> FixitySig GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcPs -> m (FixitySig GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcRn) Source # toConstr :: FixitySig GhcRn -> Constr Source # dataTypeOf :: FixitySig GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcRn -> FixitySig GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcRn -> m (FixitySig GhcRn) Source # | |||||||||||||
Data (FixitySig 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FixitySig GhcTc) Source # toConstr :: FixitySig GhcTc -> Constr Source # dataTypeOf :: FixitySig GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FixitySig GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FixitySig GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> FixitySig GhcTc -> FixitySig GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FixitySig GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FixitySig GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FixitySig GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FixitySig GhcTc -> m (FixitySig GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcPs) Source # toConstr :: HsIPBinds GhcPs -> Constr Source # dataTypeOf :: HsIPBinds GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcPs -> HsIPBinds GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcPs -> m (HsIPBinds GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcRn) Source # toConstr :: HsIPBinds GhcRn -> Constr Source # dataTypeOf :: HsIPBinds GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcRn -> HsIPBinds GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcRn -> m (HsIPBinds GhcRn) Source # | |||||||||||||
Data (HsIPBinds 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsIPBinds GhcTc) Source # toConstr :: HsIPBinds GhcTc -> Constr Source # dataTypeOf :: HsIPBinds GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsIPBinds GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsIPBinds GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsIPBinds GhcTc -> HsIPBinds GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPBinds GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsIPBinds GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPBinds GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPBinds GhcTc -> m (HsIPBinds GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcPs) Source # toConstr :: HsPatSynDir GhcPs -> Constr Source # dataTypeOf :: HsPatSynDir GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcPs -> HsPatSynDir GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcPs -> m (HsPatSynDir GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcRn) Source # toConstr :: HsPatSynDir GhcRn -> Constr Source # dataTypeOf :: HsPatSynDir GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcRn -> HsPatSynDir GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcRn -> m (HsPatSynDir GhcRn) Source # | |||||||||||||
Data (HsPatSynDir 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSynDir GhcTc) Source # toConstr :: HsPatSynDir GhcTc -> Constr Source # dataTypeOf :: HsPatSynDir GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSynDir GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSynDir GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPatSynDir GhcTc -> HsPatSynDir GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSynDir GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPatSynDir GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSynDir GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSynDir GhcTc -> m (HsPatSynDir GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcPs) Source # toConstr :: IPBind GhcPs -> Constr Source # dataTypeOf :: IPBind GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> IPBind GhcPs -> IPBind GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcPs -> m (IPBind GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcRn) Source # toConstr :: IPBind GhcRn -> Constr Source # dataTypeOf :: IPBind GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> IPBind GhcRn -> IPBind GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcRn -> m (IPBind GhcRn) Source # | |||||||||||||
Data (IPBind 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IPBind GhcTc) Source # toConstr :: IPBind GhcTc -> Constr Source # dataTypeOf :: IPBind GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IPBind GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IPBind GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> IPBind GhcTc -> IPBind GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IPBind GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IPBind GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IPBind GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IPBind GhcTc -> m (IPBind GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RecordPatSynField GhcPs) Source # toConstr :: RecordPatSynField GhcPs -> Constr Source # dataTypeOf :: RecordPatSynField GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RecordPatSynField GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RecordPatSynField GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> RecordPatSynField GhcPs -> RecordPatSynField GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RecordPatSynField GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordPatSynField GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcPs -> m (RecordPatSynField GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcPs -> m (RecordPatSynField GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcPs -> m (RecordPatSynField GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RecordPatSynField GhcRn) Source # toConstr :: RecordPatSynField GhcRn -> Constr Source # dataTypeOf :: RecordPatSynField GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RecordPatSynField GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RecordPatSynField GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> RecordPatSynField GhcRn -> RecordPatSynField GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RecordPatSynField GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordPatSynField GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcRn -> m (RecordPatSynField GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcRn -> m (RecordPatSynField GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcRn -> m (RecordPatSynField GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RecordPatSynField GhcTc) Source # toConstr :: RecordPatSynField GhcTc -> Constr Source # dataTypeOf :: RecordPatSynField GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RecordPatSynField GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RecordPatSynField GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> RecordPatSynField GhcTc -> RecordPatSynField GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecordPatSynField GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RecordPatSynField GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecordPatSynField GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcTc -> m (RecordPatSynField GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcTc -> m (RecordPatSynField GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecordPatSynField GhcTc -> m (RecordPatSynField GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcPs) Source # toConstr :: Sig GhcPs -> Constr Source # dataTypeOf :: Sig GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> Sig GhcPs -> Sig GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Sig GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcPs -> m (Sig GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcRn) Source # toConstr :: Sig GhcRn -> Constr Source # dataTypeOf :: Sig GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> Sig GhcRn -> Sig GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Sig GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcRn -> m (Sig GhcRn) Source # | |||||||||||||
Data (Sig 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sig GhcTc) Source # toConstr :: Sig GhcTc -> Constr Source # dataTypeOf :: Sig GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Sig GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sig GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> Sig GhcTc -> Sig GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sig GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Sig GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sig GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sig GhcTc -> m (Sig GhcTc) Source # | |||||||||||||
Typeable p => Data (LayoutInfo (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) -> LayoutInfo (GhcPass p) -> c (LayoutInfo (GhcPass p)) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LayoutInfo (GhcPass p)) Source # toConstr :: LayoutInfo (GhcPass p) -> Constr Source # dataTypeOf :: LayoutInfo (GhcPass p) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LayoutInfo (GhcPass p))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LayoutInfo (GhcPass p))) Source # gmapT :: (forall b. Data b => b -> b) -> LayoutInfo (GhcPass p) -> LayoutInfo (GhcPass p) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo (GhcPass p) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayoutInfo (GhcPass p) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LayoutInfo (GhcPass p) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LayoutInfo (GhcPass p) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayoutInfo (GhcPass p) -> m (LayoutInfo (GhcPass p)) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnDecl GhcPs) Source # toConstr :: AnnDecl GhcPs -> Constr Source # dataTypeOf :: AnnDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcPs -> AnnDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnDecl GhcRn) Source # toConstr :: AnnDecl GhcRn -> Constr Source # dataTypeOf :: AnnDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcRn -> AnnDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) Source # | |||||||||||||
Data (AnnDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnDecl GhcTc) Source # toConstr :: AnnDecl GhcTc -> Constr Source # dataTypeOf :: AnnDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcTc -> AnnDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnProvenance GhcPs) Source # toConstr :: AnnProvenance GhcPs -> Constr Source # dataTypeOf :: AnnProvenance GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnProvenance GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnProvenance GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> AnnProvenance GhcPs -> AnnProvenance GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnProvenance GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProvenance GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProvenance GhcPs -> m (AnnProvenance GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcPs -> m (AnnProvenance GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcPs -> m (AnnProvenance GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnProvenance GhcRn) Source # toConstr :: AnnProvenance GhcRn -> Constr Source # dataTypeOf :: AnnProvenance GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnProvenance GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnProvenance GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> AnnProvenance GhcRn -> AnnProvenance GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnProvenance GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProvenance GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProvenance GhcRn -> m (AnnProvenance GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcRn -> m (AnnProvenance GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcRn -> m (AnnProvenance GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnProvenance GhcTc) Source # toConstr :: AnnProvenance GhcTc -> Constr Source # dataTypeOf :: AnnProvenance GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnProvenance GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnProvenance GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> AnnProvenance GhcTc -> AnnProvenance GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnProvenance GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AnnProvenance GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnProvenance GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnProvenance GhcTc -> m (AnnProvenance GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcTc -> m (AnnProvenance GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnProvenance GhcTc -> m (AnnProvenance GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcPs) Source # toConstr :: ClsInstDecl GhcPs -> Constr Source # dataTypeOf :: ClsInstDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcPs -> ClsInstDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcRn) Source # toConstr :: ClsInstDecl GhcRn -> Constr Source # dataTypeOf :: ClsInstDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcRn -> ClsInstDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) Source # | |||||||||||||
Data (ClsInstDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcTc) Source # toConstr :: ClsInstDecl GhcTc -> Constr Source # dataTypeOf :: ClsInstDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcTc -> ClsInstDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcPs) Source # toConstr :: ConDecl GhcPs -> Constr Source # dataTypeOf :: ConDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcPs -> ConDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcRn) Source # toConstr :: ConDecl GhcRn -> Constr Source # dataTypeOf :: ConDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcRn -> ConDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) Source # | |||||||||||||
Data (ConDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcTc) Source # toConstr :: ConDecl GhcTc -> Constr Source # dataTypeOf :: ConDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcTc -> ConDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcPs) Source # toConstr :: DataFamInstDecl GhcPs -> Constr Source # dataTypeOf :: DataFamInstDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcPs -> DataFamInstDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcRn) Source # toConstr :: DataFamInstDecl GhcRn -> Constr Source # dataTypeOf :: DataFamInstDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcRn -> DataFamInstDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) Source # | |||||||||||||
Data (DataFamInstDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcTc) Source # toConstr :: DataFamInstDecl GhcTc -> Constr Source # dataTypeOf :: DataFamInstDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcTc -> DataFamInstDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcPs) Source # toConstr :: DefaultDecl GhcPs -> Constr Source # dataTypeOf :: DefaultDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcPs -> DefaultDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcRn) Source # toConstr :: DefaultDecl GhcRn -> Constr Source # dataTypeOf :: DefaultDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcRn -> DefaultDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) Source # | |||||||||||||
Data (DefaultDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcTc) Source # toConstr :: DefaultDecl GhcTc -> Constr Source # dataTypeOf :: DefaultDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcTc -> DefaultDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivClauseTys GhcPs) Source # toConstr :: DerivClauseTys GhcPs -> Constr Source # dataTypeOf :: DerivClauseTys GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivClauseTys GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivClauseTys GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivClauseTys GhcPs -> DerivClauseTys GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivClauseTys GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivClauseTys GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcPs -> m (DerivClauseTys GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcPs -> m (DerivClauseTys GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcPs -> m (DerivClauseTys GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivClauseTys GhcRn) Source # toConstr :: DerivClauseTys GhcRn -> Constr Source # dataTypeOf :: DerivClauseTys GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivClauseTys GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivClauseTys GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivClauseTys GhcRn -> DerivClauseTys GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivClauseTys GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivClauseTys GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcRn -> m (DerivClauseTys GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcRn -> m (DerivClauseTys GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcRn -> m (DerivClauseTys GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivClauseTys GhcTc) Source # toConstr :: DerivClauseTys GhcTc -> Constr Source # dataTypeOf :: DerivClauseTys GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivClauseTys GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivClauseTys GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivClauseTys GhcTc -> DerivClauseTys GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivClauseTys GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivClauseTys GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivClauseTys GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcTc -> m (DerivClauseTys GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcTc -> m (DerivClauseTys GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivClauseTys GhcTc -> m (DerivClauseTys GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcPs) Source # toConstr :: DerivDecl GhcPs -> Constr Source # dataTypeOf :: DerivDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcPs -> DerivDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcRn) Source # toConstr :: DerivDecl GhcRn -> Constr Source # dataTypeOf :: DerivDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcRn -> DerivDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) Source # | |||||||||||||
Data (DerivDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcTc) Source # toConstr :: DerivDecl GhcTc -> Constr Source # dataTypeOf :: DerivDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcTc -> DerivDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcPs) Source # toConstr :: DerivStrategy GhcPs -> Constr Source # dataTypeOf :: DerivStrategy GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcPs -> DerivStrategy GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcRn) Source # toConstr :: DerivStrategy GhcRn -> Constr Source # dataTypeOf :: DerivStrategy GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcRn -> DerivStrategy GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) Source # | |||||||||||||
Data (DerivStrategy 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcTc) Source # toConstr :: DerivStrategy GhcTc -> Constr Source # dataTypeOf :: DerivStrategy GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcTc -> DerivStrategy GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcPs) Source # toConstr :: FamilyDecl GhcPs -> Constr Source # dataTypeOf :: FamilyDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcPs -> FamilyDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcRn) Source # toConstr :: FamilyDecl GhcRn -> Constr Source # dataTypeOf :: FamilyDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcRn -> FamilyDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) Source # | |||||||||||||
Data (FamilyDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcTc) Source # toConstr :: FamilyDecl GhcTc -> Constr Source # dataTypeOf :: FamilyDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcTc -> FamilyDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcPs) Source # toConstr :: FamilyInfo GhcPs -> Constr Source # dataTypeOf :: FamilyInfo GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcPs -> FamilyInfo GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcRn) Source # toConstr :: FamilyInfo GhcRn -> Constr Source # dataTypeOf :: FamilyInfo GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcRn -> FamilyInfo GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) Source # | |||||||||||||
Data (FamilyInfo 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcTc) Source # toConstr :: FamilyInfo GhcTc -> Constr Source # dataTypeOf :: FamilyInfo GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcTc -> FamilyInfo GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcPs) Source # toConstr :: FamilyResultSig GhcPs -> Constr Source # dataTypeOf :: FamilyResultSig GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcPs -> FamilyResultSig GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcRn) Source # toConstr :: FamilyResultSig GhcRn -> Constr Source # dataTypeOf :: FamilyResultSig GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcRn -> FamilyResultSig GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) Source # | |||||||||||||
Data (FamilyResultSig 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcTc) Source # toConstr :: FamilyResultSig GhcTc -> Constr Source # dataTypeOf :: FamilyResultSig GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcTc -> FamilyResultSig GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcPs) Source # toConstr :: ForeignDecl GhcPs -> Constr Source # dataTypeOf :: ForeignDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcPs -> ForeignDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcRn) Source # toConstr :: ForeignDecl GhcRn -> Constr Source # dataTypeOf :: ForeignDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcRn -> ForeignDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) Source # | |||||||||||||
Data (ForeignDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcTc) Source # toConstr :: ForeignDecl GhcTc -> Constr Source # dataTypeOf :: ForeignDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcTc -> ForeignDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) Source # | |||||||||||||
Data (ForeignExport GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignExport GhcPs -> c (ForeignExport GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignExport GhcPs) Source # toConstr :: ForeignExport GhcPs -> Constr Source # dataTypeOf :: ForeignExport GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignExport GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignExport GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignExport GhcPs -> ForeignExport GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignExport GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignExport GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignExport GhcPs -> m (ForeignExport GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport GhcPs -> m (ForeignExport GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport GhcPs -> m (ForeignExport GhcPs) Source # | |||||||||||||
Data (ForeignExport GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignExport GhcRn -> c (ForeignExport GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignExport GhcRn) Source # toConstr :: ForeignExport GhcRn -> Constr Source # dataTypeOf :: ForeignExport GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignExport GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignExport GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignExport GhcRn -> ForeignExport GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignExport GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignExport GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignExport GhcRn -> m (ForeignExport GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport GhcRn -> m (ForeignExport GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport GhcRn -> m (ForeignExport GhcRn) Source # | |||||||||||||
Data (ForeignExport GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignExport GhcTc -> c (ForeignExport GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignExport GhcTc) Source # toConstr :: ForeignExport GhcTc -> Constr Source # dataTypeOf :: ForeignExport GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignExport GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignExport GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignExport GhcTc -> ForeignExport GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignExport GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignExport GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignExport GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignExport GhcTc -> m (ForeignExport GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport GhcTc -> m (ForeignExport GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignExport GhcTc -> m (ForeignExport GhcTc) Source # | |||||||||||||
Data (ForeignImport GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignImport GhcPs -> c (ForeignImport GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignImport GhcPs) Source # toConstr :: ForeignImport GhcPs -> Constr Source # dataTypeOf :: ForeignImport GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignImport GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignImport GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignImport GhcPs -> ForeignImport GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignImport GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignImport GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignImport GhcPs -> m (ForeignImport GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport GhcPs -> m (ForeignImport GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport GhcPs -> m (ForeignImport GhcPs) Source # | |||||||||||||
Data (ForeignImport GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignImport GhcRn -> c (ForeignImport GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignImport GhcRn) Source # toConstr :: ForeignImport GhcRn -> Constr Source # dataTypeOf :: ForeignImport GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignImport GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignImport GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignImport GhcRn -> ForeignImport GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignImport GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignImport GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignImport GhcRn -> m (ForeignImport GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport GhcRn -> m (ForeignImport GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport GhcRn -> m (ForeignImport GhcRn) Source # | |||||||||||||
Data (ForeignImport GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForeignImport GhcTc -> c (ForeignImport GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignImport GhcTc) Source # toConstr :: ForeignImport GhcTc -> Constr Source # dataTypeOf :: ForeignImport GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignImport GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignImport GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ForeignImport GhcTc -> ForeignImport GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignImport GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ForeignImport GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignImport GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignImport GhcTc -> m (ForeignImport GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport GhcTc -> m (ForeignImport GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignImport GhcTc -> m (ForeignImport GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FunDep GhcPs) Source # toConstr :: FunDep GhcPs -> Constr Source # dataTypeOf :: FunDep GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FunDep GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FunDep GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> FunDep GhcPs -> FunDep GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FunDep GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep GhcPs -> m (FunDep GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcPs -> m (FunDep GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcPs -> m (FunDep GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FunDep GhcRn) Source # toConstr :: FunDep GhcRn -> Constr Source # dataTypeOf :: FunDep GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FunDep GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FunDep GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> FunDep GhcRn -> FunDep GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FunDep GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep GhcRn -> m (FunDep GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcRn -> m (FunDep GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcRn -> m (FunDep GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FunDep GhcTc) Source # toConstr :: FunDep GhcTc -> Constr Source # dataTypeOf :: FunDep GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FunDep GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FunDep GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> FunDep GhcTc -> FunDep GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FunDep GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep GhcTc -> m (FunDep GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcTc -> m (FunDep GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep GhcTc -> m (FunDep GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDeclGADTDetails GhcPs) Source # toConstr :: HsConDeclGADTDetails GhcPs -> Constr Source # dataTypeOf :: HsConDeclGADTDetails GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDeclGADTDetails GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDeclGADTDetails GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsConDeclGADTDetails GhcPs -> HsConDeclGADTDetails GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcPs -> m (HsConDeclGADTDetails GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcPs -> m (HsConDeclGADTDetails GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcPs -> m (HsConDeclGADTDetails GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDeclGADTDetails GhcRn) Source # toConstr :: HsConDeclGADTDetails GhcRn -> Constr Source # dataTypeOf :: HsConDeclGADTDetails GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDeclGADTDetails GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDeclGADTDetails GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsConDeclGADTDetails GhcRn -> HsConDeclGADTDetails GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcRn -> m (HsConDeclGADTDetails GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcRn -> m (HsConDeclGADTDetails GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcRn -> m (HsConDeclGADTDetails GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDeclGADTDetails GhcTc) Source # toConstr :: HsConDeclGADTDetails GhcTc -> Constr Source # dataTypeOf :: HsConDeclGADTDetails GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDeclGADTDetails GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDeclGADTDetails GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsConDeclGADTDetails GhcTc -> HsConDeclGADTDetails GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDeclGADTDetails GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDeclGADTDetails GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcTc -> m (HsConDeclGADTDetails GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcTc -> m (HsConDeclGADTDetails GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDeclGADTDetails GhcTc -> m (HsConDeclGADTDetails GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcPs) Source # toConstr :: HsDataDefn GhcPs -> Constr Source # dataTypeOf :: HsDataDefn GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcPs -> HsDataDefn GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcRn) Source # toConstr :: HsDataDefn GhcRn -> Constr Source # dataTypeOf :: HsDataDefn GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcRn -> HsDataDefn GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) Source # | |||||||||||||
Data (HsDataDefn 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcTc) Source # toConstr :: HsDataDefn GhcTc -> Constr Source # dataTypeOf :: HsDataDefn GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcTc -> HsDataDefn GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcPs) Source # toConstr :: HsDecl GhcPs -> Constr Source # dataTypeOf :: HsDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcPs -> HsDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcRn) Source # toConstr :: HsDecl GhcRn -> Constr Source # dataTypeOf :: HsDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcRn -> HsDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) Source # | |||||||||||||
Data (HsDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcTc) Source # toConstr :: HsDecl GhcTc -> Constr Source # dataTypeOf :: HsDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcTc -> HsDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcPs) Source # toConstr :: HsDerivingClause GhcPs -> Constr Source # dataTypeOf :: HsDerivingClause GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcPs -> HsDerivingClause GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcRn) Source # toConstr :: HsDerivingClause GhcRn -> Constr Source # dataTypeOf :: HsDerivingClause GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcRn -> HsDerivingClause GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) Source # | |||||||||||||
Data (HsDerivingClause 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcTc) Source # toConstr :: HsDerivingClause GhcTc -> Constr Source # dataTypeOf :: HsDerivingClause GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcTc -> HsDerivingClause GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcPs) Source # toConstr :: HsGroup GhcPs -> Constr Source # dataTypeOf :: HsGroup GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcPs -> HsGroup GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcRn) Source # toConstr :: HsGroup GhcRn -> Constr Source # dataTypeOf :: HsGroup GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcRn -> HsGroup GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source # | |||||||||||||
Data (HsGroup 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcTc) Source # toConstr :: HsGroup GhcTc -> Constr Source # dataTypeOf :: HsGroup GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcTc -> HsGroup GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcPs) Source # toConstr :: InjectivityAnn GhcPs -> Constr Source # dataTypeOf :: InjectivityAnn GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcPs -> InjectivityAnn GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcRn) Source # toConstr :: InjectivityAnn GhcRn -> Constr Source # dataTypeOf :: InjectivityAnn GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcRn -> InjectivityAnn GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source # | |||||||||||||
Data (InjectivityAnn 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcTc) Source # toConstr :: InjectivityAnn GhcTc -> Constr Source # dataTypeOf :: InjectivityAnn GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcTc -> InjectivityAnn GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcPs) Source # toConstr :: InstDecl GhcPs -> Constr Source # dataTypeOf :: InstDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcPs -> InstDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcRn) Source # toConstr :: InstDecl GhcRn -> Constr Source # dataTypeOf :: InstDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcRn -> InstDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source # | |||||||||||||
Data (InstDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcTc) Source # toConstr :: InstDecl GhcTc -> Constr Source # dataTypeOf :: InstDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcTc -> InstDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcPs) Source # toConstr :: RoleAnnotDecl GhcPs -> Constr Source # dataTypeOf :: RoleAnnotDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcPs -> RoleAnnotDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcRn) Source # toConstr :: RoleAnnotDecl GhcRn -> Constr Source # dataTypeOf :: RoleAnnotDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcRn -> RoleAnnotDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source # | |||||||||||||
Data (RoleAnnotDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcTc) Source # toConstr :: RoleAnnotDecl GhcTc -> Constr Source # dataTypeOf :: RoleAnnotDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcTc -> RoleAnnotDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcPs) Source # toConstr :: RuleBndr GhcPs -> Constr Source # dataTypeOf :: RuleBndr GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcPs -> RuleBndr GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcRn) Source # toConstr :: RuleBndr GhcRn -> Constr Source # dataTypeOf :: RuleBndr GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcRn -> RuleBndr GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source # | |||||||||||||
Data (RuleBndr 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcTc) Source # toConstr :: RuleBndr GhcTc -> Constr Source # dataTypeOf :: RuleBndr GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcTc -> RuleBndr GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcPs) Source # toConstr :: RuleDecl GhcPs -> Constr Source # dataTypeOf :: RuleDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcPs -> RuleDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcRn) Source # toConstr :: RuleDecl GhcRn -> Constr Source # dataTypeOf :: RuleDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcRn -> RuleDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source # | |||||||||||||
Data (RuleDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcTc) Source # toConstr :: RuleDecl GhcTc -> Constr Source # dataTypeOf :: RuleDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcTc -> RuleDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcPs) Source # toConstr :: RuleDecls GhcPs -> Constr Source # dataTypeOf :: RuleDecls GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcPs -> RuleDecls GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcRn) Source # toConstr :: RuleDecls GhcRn -> Constr Source # dataTypeOf :: RuleDecls GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcRn -> RuleDecls GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source # | |||||||||||||
Data (RuleDecls 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcTc) Source # toConstr :: RuleDecls GhcTc -> Constr Source # dataTypeOf :: RuleDecls GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcTc -> RuleDecls GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcPs) Source # toConstr :: SpliceDecl GhcPs -> Constr Source # dataTypeOf :: SpliceDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcPs -> SpliceDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcRn) Source # toConstr :: SpliceDecl GhcRn -> Constr Source # dataTypeOf :: SpliceDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcRn -> SpliceDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source # | |||||||||||||
Data (SpliceDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcTc) Source # toConstr :: SpliceDecl GhcTc -> Constr Source # dataTypeOf :: SpliceDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcTc -> SpliceDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcPs) Source # toConstr :: StandaloneKindSig GhcPs -> Constr Source # dataTypeOf :: StandaloneKindSig GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcPs -> StandaloneKindSig GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcRn) Source # toConstr :: StandaloneKindSig GhcRn -> Constr Source # dataTypeOf :: StandaloneKindSig GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcRn -> StandaloneKindSig GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcTc) Source # toConstr :: StandaloneKindSig GhcTc -> Constr Source # dataTypeOf :: StandaloneKindSig GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcTc -> StandaloneKindSig GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcPs) Source # toConstr :: TyClDecl GhcPs -> Constr Source # dataTypeOf :: TyClDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcPs -> TyClDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcRn) Source # toConstr :: TyClDecl GhcRn -> Constr Source # dataTypeOf :: TyClDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcRn -> TyClDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source # | |||||||||||||
Data (TyClDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcTc) Source # toConstr :: TyClDecl GhcTc -> Constr Source # dataTypeOf :: TyClDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcTc -> TyClDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcPs) Source # toConstr :: TyClGroup GhcPs -> Constr Source # dataTypeOf :: TyClGroup GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcPs -> TyClGroup GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcRn) Source # toConstr :: TyClGroup GhcRn -> Constr Source # dataTypeOf :: TyClGroup GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcRn -> TyClGroup GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source # | |||||||||||||
Data (TyClGroup 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcTc) Source # toConstr :: TyClGroup GhcTc -> Constr Source # dataTypeOf :: TyClGroup GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcTc -> TyClGroup GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcPs) Source # toConstr :: TyFamInstDecl GhcPs -> Constr Source # dataTypeOf :: TyFamInstDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcPs -> TyFamInstDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcRn) Source # toConstr :: TyFamInstDecl GhcRn -> Constr Source # dataTypeOf :: TyFamInstDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcRn -> TyFamInstDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source # | |||||||||||||
Data (TyFamInstDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcTc) Source # toConstr :: TyFamInstDecl GhcTc -> Constr Source # dataTypeOf :: TyFamInstDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcTc -> TyFamInstDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcPs) Source # toConstr :: WarnDecl GhcPs -> Constr Source # dataTypeOf :: WarnDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcPs -> WarnDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcRn) Source # toConstr :: WarnDecl GhcRn -> Constr Source # dataTypeOf :: WarnDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcRn -> WarnDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source # | |||||||||||||
Data (WarnDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcTc) Source # toConstr :: WarnDecl GhcTc -> Constr Source # dataTypeOf :: WarnDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcTc -> WarnDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcPs) Source # toConstr :: WarnDecls GhcPs -> Constr Source # dataTypeOf :: WarnDecls GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcPs -> WarnDecls GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcRn) Source # toConstr :: WarnDecls GhcRn -> Constr Source # dataTypeOf :: WarnDecls GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcRn -> WarnDecls GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source # | |||||||||||||
Data (WarnDecls 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcTc) Source # toConstr :: WarnDecls GhcTc -> Constr Source # dataTypeOf :: WarnDecls GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcTc -> WarnDecls GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcPs) Source # toConstr :: ApplicativeArg GhcPs -> Constr Source # dataTypeOf :: ApplicativeArg GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcPs -> ApplicativeArg GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcRn) Source # toConstr :: ApplicativeArg GhcRn -> Constr Source # dataTypeOf :: ApplicativeArg GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcRn -> ApplicativeArg GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source # | |||||||||||||
Data (ApplicativeArg 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcTc) Source # toConstr :: ApplicativeArg GhcTc -> Constr Source # dataTypeOf :: ApplicativeArg GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcTc -> ApplicativeArg GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcPs) Source # toConstr :: ArithSeqInfo GhcPs -> Constr Source # dataTypeOf :: ArithSeqInfo GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcPs -> ArithSeqInfo GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcRn) Source # toConstr :: ArithSeqInfo GhcRn -> Constr Source # dataTypeOf :: ArithSeqInfo GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcRn -> ArithSeqInfo GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source # | |||||||||||||
Data (ArithSeqInfo 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcTc) Source # toConstr :: ArithSeqInfo GhcTc -> Constr Source # dataTypeOf :: ArithSeqInfo GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcTc -> ArithSeqInfo GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source # | |||||||||||||
Data (DotFieldOcc GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DotFieldOcc GhcPs -> c (DotFieldOcc GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DotFieldOcc GhcPs) Source # toConstr :: DotFieldOcc GhcPs -> Constr Source # dataTypeOf :: DotFieldOcc GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DotFieldOcc GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DotFieldOcc GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> DotFieldOcc GhcPs -> DotFieldOcc GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DotFieldOcc GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DotFieldOcc GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DotFieldOcc GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DotFieldOcc GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcPs -> m (DotFieldOcc GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcPs -> m (DotFieldOcc GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcPs -> m (DotFieldOcc GhcPs) Source # | |||||||||||||
Data (DotFieldOcc GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DotFieldOcc GhcRn -> c (DotFieldOcc GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DotFieldOcc GhcRn) Source # toConstr :: DotFieldOcc GhcRn -> Constr Source # dataTypeOf :: DotFieldOcc GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DotFieldOcc GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DotFieldOcc GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> DotFieldOcc GhcRn -> DotFieldOcc GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DotFieldOcc GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DotFieldOcc GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DotFieldOcc GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DotFieldOcc GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcRn -> m (DotFieldOcc GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcRn -> m (DotFieldOcc GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcRn -> m (DotFieldOcc GhcRn) Source # | |||||||||||||
Data (DotFieldOcc GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DotFieldOcc GhcTc -> c (DotFieldOcc GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DotFieldOcc GhcTc) Source # toConstr :: DotFieldOcc GhcTc -> Constr Source # dataTypeOf :: DotFieldOcc GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DotFieldOcc GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DotFieldOcc GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> DotFieldOcc GhcTc -> DotFieldOcc GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DotFieldOcc GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DotFieldOcc GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DotFieldOcc GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DotFieldOcc GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcTc -> m (DotFieldOcc GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcTc -> m (DotFieldOcc GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DotFieldOcc GhcTc -> m (DotFieldOcc GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLabelStrings GhcPs) Source # toConstr :: FieldLabelStrings GhcPs -> Constr Source # dataTypeOf :: FieldLabelStrings GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLabelStrings GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLabelStrings GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> FieldLabelStrings GhcPs -> FieldLabelStrings GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FieldLabelStrings GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLabelStrings GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcPs -> m (FieldLabelStrings GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcPs -> m (FieldLabelStrings GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcPs -> m (FieldLabelStrings GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLabelStrings GhcRn) Source # toConstr :: FieldLabelStrings GhcRn -> Constr Source # dataTypeOf :: FieldLabelStrings GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLabelStrings GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLabelStrings GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> FieldLabelStrings GhcRn -> FieldLabelStrings GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FieldLabelStrings GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLabelStrings GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcRn -> m (FieldLabelStrings GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcRn -> m (FieldLabelStrings GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcRn -> m (FieldLabelStrings GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLabelStrings GhcTc) Source # toConstr :: FieldLabelStrings GhcTc -> Constr Source # dataTypeOf :: FieldLabelStrings GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLabelStrings GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLabelStrings GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> FieldLabelStrings GhcTc -> FieldLabelStrings GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLabelStrings GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FieldLabelStrings GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLabelStrings GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcTc -> m (FieldLabelStrings GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcTc -> m (FieldLabelStrings GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLabelStrings GhcTc -> m (FieldLabelStrings GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcPs) Source # toConstr :: HsCmd GhcPs -> Constr Source # dataTypeOf :: HsCmd GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcPs -> HsCmd GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcRn) Source # toConstr :: HsCmd GhcRn -> Constr Source # dataTypeOf :: HsCmd GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcRn -> HsCmd GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source # | |||||||||||||
Data (HsCmd 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcTc) Source # toConstr :: HsCmd GhcTc -> Constr Source # dataTypeOf :: HsCmd GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcTc -> HsCmd GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcPs) Source # toConstr :: HsCmdTop GhcPs -> Constr Source # dataTypeOf :: HsCmdTop GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcPs -> HsCmdTop GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcRn) Source # toConstr :: HsCmdTop GhcRn -> Constr Source # dataTypeOf :: HsCmdTop GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcRn -> HsCmdTop GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source # | |||||||||||||
Data (HsCmdTop 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcTc) Source # toConstr :: HsCmdTop GhcTc -> Constr Source # dataTypeOf :: HsCmdTop GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcTc -> HsCmdTop GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcPs) Source # toConstr :: HsExpr GhcPs -> Constr Source # dataTypeOf :: HsExpr GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcPs -> HsExpr GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcRn) Source # toConstr :: HsExpr GhcRn -> Constr Source # dataTypeOf :: HsExpr GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcRn -> HsExpr GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source # | |||||||||||||
Data (HsExpr 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcTc) Source # toConstr :: HsExpr GhcTc -> Constr Source # dataTypeOf :: HsExpr GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcTc -> HsExpr GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext GhcPs) Source # toConstr :: HsMatchContext GhcPs -> Constr Source # dataTypeOf :: HsMatchContext GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsMatchContext GhcPs -> HsMatchContext GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext GhcPs -> m (HsMatchContext GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcPs -> m (HsMatchContext GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcPs -> m (HsMatchContext GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext GhcRn) Source # toConstr :: HsMatchContext GhcRn -> Constr Source # dataTypeOf :: HsMatchContext GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsMatchContext GhcRn -> HsMatchContext GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext GhcRn -> m (HsMatchContext GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcRn -> m (HsMatchContext GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcRn -> m (HsMatchContext GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsMatchContext GhcTc) Source # toConstr :: HsMatchContext GhcTc -> Constr Source # dataTypeOf :: HsMatchContext GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsMatchContext GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsMatchContext GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsMatchContext GhcTc -> HsMatchContext GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsMatchContext GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsMatchContext GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsMatchContext GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsMatchContext GhcTc -> m (HsMatchContext GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcTc -> m (HsMatchContext GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsMatchContext GhcTc -> m (HsMatchContext GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPragE GhcPs) Source # toConstr :: HsPragE GhcPs -> Constr Source # dataTypeOf :: HsPragE GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPragE GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPragE GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPragE GhcPs -> HsPragE GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPragE GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPragE GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPragE GhcPs -> m (HsPragE GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcPs -> m (HsPragE GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcPs -> m (HsPragE GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPragE GhcRn) Source # toConstr :: HsPragE GhcRn -> Constr Source # dataTypeOf :: HsPragE GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPragE GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPragE GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPragE GhcRn -> HsPragE GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPragE GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPragE GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPragE GhcRn -> m (HsPragE GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcRn -> m (HsPragE GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcRn -> m (HsPragE GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPragE GhcTc) Source # toConstr :: HsPragE GhcTc -> Constr Source # dataTypeOf :: HsPragE GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPragE GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPragE GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPragE GhcTc -> HsPragE GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPragE GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPragE GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPragE GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPragE GhcTc -> m (HsPragE GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcTc -> m (HsPragE GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPragE GhcTc -> m (HsPragE GhcTc) Source # | |||||||||||||
Data (HsQuote GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsQuote GhcPs -> c (HsQuote GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsQuote GhcPs) Source # toConstr :: HsQuote GhcPs -> Constr Source # dataTypeOf :: HsQuote GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsQuote GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsQuote GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsQuote GhcPs -> HsQuote GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsQuote GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsQuote GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsQuote GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsQuote GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsQuote GhcPs -> m (HsQuote GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQuote GhcPs -> m (HsQuote GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQuote GhcPs -> m (HsQuote GhcPs) Source # | |||||||||||||
Data (HsQuote GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsQuote GhcRn -> c (HsQuote GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsQuote GhcRn) Source # toConstr :: HsQuote GhcRn -> Constr Source # dataTypeOf :: HsQuote GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsQuote GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsQuote GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsQuote GhcRn -> HsQuote GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsQuote GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsQuote GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsQuote GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsQuote GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsQuote GhcRn -> m (HsQuote GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQuote GhcRn -> m (HsQuote GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQuote GhcRn -> m (HsQuote GhcRn) Source # | |||||||||||||
Data (HsQuote GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsQuote GhcTc -> c (HsQuote GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsQuote GhcTc) Source # toConstr :: HsQuote GhcTc -> Constr Source # dataTypeOf :: HsQuote GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsQuote GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsQuote GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsQuote GhcTc -> HsQuote GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsQuote GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsQuote GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsQuote GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsQuote GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsQuote GhcTc -> m (HsQuote GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQuote GhcTc -> m (HsQuote GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsQuote GhcTc -> m (HsQuote GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext GhcPs) Source # toConstr :: HsStmtContext GhcPs -> Constr Source # dataTypeOf :: HsStmtContext GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsStmtContext GhcPs -> HsStmtContext GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext GhcPs -> m (HsStmtContext GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcPs -> m (HsStmtContext GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcPs -> m (HsStmtContext GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext GhcRn) Source # toConstr :: HsStmtContext GhcRn -> Constr Source # dataTypeOf :: HsStmtContext GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsStmtContext GhcRn -> HsStmtContext GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext GhcRn -> m (HsStmtContext GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcRn -> m (HsStmtContext GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcRn -> m (HsStmtContext GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsStmtContext GhcTc) Source # toConstr :: HsStmtContext GhcTc -> Constr Source # dataTypeOf :: HsStmtContext GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsStmtContext GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsStmtContext GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsStmtContext GhcTc -> HsStmtContext GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsStmtContext GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsStmtContext GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsStmtContext GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsStmtContext GhcTc -> m (HsStmtContext GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcTc -> m (HsStmtContext GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsStmtContext GhcTc -> m (HsStmtContext GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcPs) Source # toConstr :: HsTupArg GhcPs -> Constr Source # dataTypeOf :: HsTupArg GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcPs -> HsTupArg GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcRn) Source # toConstr :: HsTupArg GhcRn -> Constr Source # dataTypeOf :: HsTupArg GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcRn -> HsTupArg GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source # | |||||||||||||
Data (HsTupArg 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcTc) Source # toConstr :: HsTupArg GhcTc -> Constr Source # dataTypeOf :: HsTupArg GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcTc -> HsTupArg GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source # | |||||||||||||
Data (HsUntypedSplice GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsUntypedSplice GhcPs -> c (HsUntypedSplice GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsUntypedSplice GhcPs) Source # toConstr :: HsUntypedSplice GhcPs -> Constr Source # dataTypeOf :: HsUntypedSplice GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsUntypedSplice GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsUntypedSplice GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsUntypedSplice GhcPs -> HsUntypedSplice GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsUntypedSplice GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsUntypedSplice GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsUntypedSplice GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsUntypedSplice GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcPs -> m (HsUntypedSplice GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcPs -> m (HsUntypedSplice GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcPs -> m (HsUntypedSplice GhcPs) Source # | |||||||||||||
Data (HsUntypedSplice GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsUntypedSplice GhcRn -> c (HsUntypedSplice GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsUntypedSplice GhcRn) Source # toConstr :: HsUntypedSplice GhcRn -> Constr Source # dataTypeOf :: HsUntypedSplice GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsUntypedSplice GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsUntypedSplice GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsUntypedSplice GhcRn -> HsUntypedSplice GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsUntypedSplice GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsUntypedSplice GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsUntypedSplice GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsUntypedSplice GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcRn -> m (HsUntypedSplice GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcRn -> m (HsUntypedSplice GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcRn -> m (HsUntypedSplice GhcRn) Source # | |||||||||||||
Data (HsUntypedSplice GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsUntypedSplice GhcTc -> c (HsUntypedSplice GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsUntypedSplice GhcTc) Source # toConstr :: HsUntypedSplice GhcTc -> Constr Source # dataTypeOf :: HsUntypedSplice GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsUntypedSplice GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsUntypedSplice GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsUntypedSplice GhcTc -> HsUntypedSplice GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsUntypedSplice GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsUntypedSplice GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsUntypedSplice GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsUntypedSplice GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcTc -> m (HsUntypedSplice GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcTc -> m (HsUntypedSplice GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsUntypedSplice GhcTc -> m (HsUntypedSplice GhcTc) Source # | |||||||||||||
Data (LHsRecUpdFields GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsRecUpdFields GhcPs -> c (LHsRecUpdFields GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsRecUpdFields GhcPs) Source # toConstr :: LHsRecUpdFields GhcPs -> Constr Source # dataTypeOf :: LHsRecUpdFields GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsRecUpdFields GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsRecUpdFields GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> LHsRecUpdFields GhcPs -> LHsRecUpdFields GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsRecUpdFields GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsRecUpdFields GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LHsRecUpdFields GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsRecUpdFields GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcPs -> m (LHsRecUpdFields GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcPs -> m (LHsRecUpdFields GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcPs -> m (LHsRecUpdFields GhcPs) Source # | |||||||||||||
Data (LHsRecUpdFields GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsRecUpdFields GhcRn -> c (LHsRecUpdFields GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsRecUpdFields GhcRn) Source # toConstr :: LHsRecUpdFields GhcRn -> Constr Source # dataTypeOf :: LHsRecUpdFields GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsRecUpdFields GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsRecUpdFields GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> LHsRecUpdFields GhcRn -> LHsRecUpdFields GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsRecUpdFields GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsRecUpdFields GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LHsRecUpdFields GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsRecUpdFields GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcRn -> m (LHsRecUpdFields GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcRn -> m (LHsRecUpdFields GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcRn -> m (LHsRecUpdFields GhcRn) Source # | |||||||||||||
Data (LHsRecUpdFields GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsRecUpdFields GhcTc -> c (LHsRecUpdFields GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsRecUpdFields GhcTc) Source # toConstr :: LHsRecUpdFields GhcTc -> Constr Source # dataTypeOf :: LHsRecUpdFields GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsRecUpdFields GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsRecUpdFields GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> LHsRecUpdFields GhcTc -> LHsRecUpdFields GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsRecUpdFields GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsRecUpdFields GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LHsRecUpdFields GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsRecUpdFields GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcTc -> m (LHsRecUpdFields GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcTc -> m (LHsRecUpdFields GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsRecUpdFields GhcTc -> m (LHsRecUpdFields GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcPs) Source # toConstr :: IE GhcPs -> Constr Source # dataTypeOf :: IE GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> IE GhcPs -> IE GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IE GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcRn) Source # toConstr :: IE GhcRn -> Constr Source # dataTypeOf :: IE GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> IE GhcRn -> IE GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IE GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source # | |||||||||||||
Data (IE 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcTc) Source # toConstr :: IE GhcTc -> Constr Source # dataTypeOf :: IE GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> IE GhcTc -> IE GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IE GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source # | |||||||||||||
Data (IEWrappedName GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName GhcPs -> c (IEWrappedName GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName GhcPs) Source # toConstr :: IEWrappedName GhcPs -> Constr Source # dataTypeOf :: IEWrappedName GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> IEWrappedName GhcPs -> IEWrappedName GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName GhcPs -> m (IEWrappedName GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcPs -> m (IEWrappedName GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcPs -> m (IEWrappedName GhcPs) Source # | |||||||||||||
Data (IEWrappedName GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName GhcRn -> c (IEWrappedName GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName GhcRn) Source # toConstr :: IEWrappedName GhcRn -> Constr Source # dataTypeOf :: IEWrappedName GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> IEWrappedName GhcRn -> IEWrappedName GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName GhcRn -> m (IEWrappedName GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcRn -> m (IEWrappedName GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcRn -> m (IEWrappedName GhcRn) Source # | |||||||||||||
Data (IEWrappedName GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IEWrappedName GhcTc -> c (IEWrappedName GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IEWrappedName GhcTc) Source # toConstr :: IEWrappedName GhcTc -> Constr Source # dataTypeOf :: IEWrappedName GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IEWrappedName GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IEWrappedName GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> IEWrappedName GhcTc -> IEWrappedName GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IEWrappedName GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> IEWrappedName GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> IEWrappedName GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IEWrappedName GhcTc -> m (IEWrappedName GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcTc -> m (IEWrappedName GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IEWrappedName GhcTc -> m (IEWrappedName GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcPs) Source # toConstr :: ImportDecl GhcPs -> Constr Source # dataTypeOf :: ImportDecl GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcPs -> ImportDecl GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcRn) Source # toConstr :: ImportDecl GhcRn -> Constr Source # dataTypeOf :: ImportDecl GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcRn -> ImportDecl GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source # | |||||||||||||
Data (ImportDecl 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcTc) Source # toConstr :: ImportDecl GhcTc -> Constr Source # dataTypeOf :: ImportDecl GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcTc -> ImportDecl GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcPs) Source # toConstr :: HsLit GhcPs -> Constr Source # dataTypeOf :: HsLit GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLit GhcPs -> HsLit GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcRn) Source # toConstr :: HsLit GhcRn -> Constr Source # dataTypeOf :: HsLit GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLit GhcRn -> HsLit GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source # | |||||||||||||
Data (HsLit 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcTc) Source # toConstr :: HsLit GhcTc -> Constr Source # dataTypeOf :: HsLit GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLit GhcTc -> HsLit GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcPs) Source # toConstr :: HsOverLit GhcPs -> Constr Source # dataTypeOf :: HsOverLit GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcPs -> HsOverLit GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcRn) Source # toConstr :: HsOverLit GhcRn -> Constr Source # dataTypeOf :: HsOverLit GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcRn -> HsOverLit GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source # | |||||||||||||
Data (HsOverLit 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcTc) Source # toConstr :: HsOverLit GhcTc -> Constr Source # dataTypeOf :: HsOverLit GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcTc -> HsOverLit GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source # | |||||||||||||
Data (HsConPatTyArg GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConPatTyArg GhcPs -> c (HsConPatTyArg GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConPatTyArg GhcPs) Source # toConstr :: HsConPatTyArg GhcPs -> Constr Source # dataTypeOf :: HsConPatTyArg GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConPatTyArg GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConPatTyArg GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsConPatTyArg GhcPs -> HsConPatTyArg GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsConPatTyArg GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConPatTyArg GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcPs -> m (HsConPatTyArg GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcPs -> m (HsConPatTyArg GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcPs -> m (HsConPatTyArg GhcPs) Source # | |||||||||||||
Data (HsConPatTyArg GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConPatTyArg GhcRn -> c (HsConPatTyArg GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConPatTyArg GhcRn) Source # toConstr :: HsConPatTyArg GhcRn -> Constr Source # dataTypeOf :: HsConPatTyArg GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConPatTyArg GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConPatTyArg GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsConPatTyArg GhcRn -> HsConPatTyArg GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsConPatTyArg GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConPatTyArg GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcRn -> m (HsConPatTyArg GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcRn -> m (HsConPatTyArg GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcRn -> m (HsConPatTyArg GhcRn) Source # | |||||||||||||
Data (HsConPatTyArg GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConPatTyArg GhcTc -> c (HsConPatTyArg GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConPatTyArg GhcTc) Source # toConstr :: HsConPatTyArg GhcTc -> Constr Source # dataTypeOf :: HsConPatTyArg GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConPatTyArg GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConPatTyArg GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsConPatTyArg GhcTc -> HsConPatTyArg GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsConPatTyArg GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConPatTyArg GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcTc -> m (HsConPatTyArg GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcTc -> m (HsConPatTyArg GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcTc -> m (HsConPatTyArg GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcPs) Source # toConstr :: Pat GhcPs -> Constr Source # dataTypeOf :: Pat GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> Pat GhcPs -> Pat GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcRn) Source # toConstr :: Pat GhcRn -> Constr Source # dataTypeOf :: Pat GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> Pat GhcRn -> Pat GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source # | |||||||||||||
Data (Pat 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcTc) Source # toConstr :: Pat GhcTc -> Constr Source # dataTypeOf :: Pat GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> Pat GhcTc -> Pat GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcPs) Source # toConstr :: AmbiguousFieldOcc GhcPs -> Constr Source # dataTypeOf :: AmbiguousFieldOcc GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcPs -> AmbiguousFieldOcc GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcRn) Source # toConstr :: AmbiguousFieldOcc GhcRn -> Constr Source # dataTypeOf :: AmbiguousFieldOcc GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcRn -> AmbiguousFieldOcc GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source # | |||||||||||||
Data (AmbiguousFieldOcc 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcTc) Source # toConstr :: AmbiguousFieldOcc GhcTc -> Constr Source # dataTypeOf :: AmbiguousFieldOcc GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcTc -> AmbiguousFieldOcc GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcPs) Source # toConstr :: ConDeclField GhcPs -> Constr Source # dataTypeOf :: ConDeclField GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcPs -> ConDeclField GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcRn) Source # toConstr :: ConDeclField GhcRn -> Constr Source # dataTypeOf :: ConDeclField GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcRn -> ConDeclField GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source # | |||||||||||||
Data (ConDeclField 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcTc) Source # toConstr :: ConDeclField GhcTc -> Constr Source # dataTypeOf :: ConDeclField GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcTc -> ConDeclField GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcPs) Source # toConstr :: FieldOcc GhcPs -> Constr Source # dataTypeOf :: FieldOcc GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcPs -> FieldOcc GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcRn) Source # toConstr :: FieldOcc GhcRn -> Constr Source # dataTypeOf :: FieldOcc GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcRn -> FieldOcc GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source # | |||||||||||||
Data (FieldOcc 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcTc) Source # toConstr :: FieldOcc GhcTc -> Constr Source # dataTypeOf :: FieldOcc GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcTc -> FieldOcc GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcPs) Source # toConstr :: HsArrow GhcPs -> Constr Source # dataTypeOf :: HsArrow GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcPs -> HsArrow GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcRn) Source # toConstr :: HsArrow GhcRn -> Constr Source # dataTypeOf :: HsArrow GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcRn -> HsArrow GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcTc) Source # toConstr :: HsArrow GhcTc -> Constr Source # dataTypeOf :: HsArrow GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcTc -> HsArrow GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) Source # | |||||||||||||
Data (HsBndrVis GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBndrVis GhcPs -> c (HsBndrVis GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBndrVis GhcPs) Source # toConstr :: HsBndrVis GhcPs -> Constr Source # dataTypeOf :: HsBndrVis GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBndrVis GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBndrVis GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsBndrVis GhcPs -> HsBndrVis GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsBndrVis GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBndrVis GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBndrVis GhcPs -> m (HsBndrVis GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcPs -> m (HsBndrVis GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcPs -> m (HsBndrVis GhcPs) Source # | |||||||||||||
Data (HsBndrVis GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBndrVis GhcRn -> c (HsBndrVis GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBndrVis GhcRn) Source # toConstr :: HsBndrVis GhcRn -> Constr Source # dataTypeOf :: HsBndrVis GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBndrVis GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBndrVis GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsBndrVis GhcRn -> HsBndrVis GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsBndrVis GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBndrVis GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBndrVis GhcRn -> m (HsBndrVis GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcRn -> m (HsBndrVis GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcRn -> m (HsBndrVis GhcRn) Source # | |||||||||||||
Data (HsBndrVis GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBndrVis GhcTc -> c (HsBndrVis GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBndrVis GhcTc) Source # toConstr :: HsBndrVis GhcTc -> Constr Source # dataTypeOf :: HsBndrVis GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBndrVis GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBndrVis GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsBndrVis GhcTc -> HsBndrVis GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsBndrVis GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBndrVis GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBndrVis GhcTc -> m (HsBndrVis GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcTc -> m (HsBndrVis GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcTc -> m (HsBndrVis GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcPs) Source # toConstr :: HsForAllTelescope GhcPs -> Constr Source # dataTypeOf :: HsForAllTelescope GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcPs -> HsForAllTelescope GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcRn) Source # toConstr :: HsForAllTelescope GhcRn -> Constr Source # dataTypeOf :: HsForAllTelescope GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcRn -> HsForAllTelescope GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcTc) Source # toConstr :: HsForAllTelescope GhcTc -> Constr Source # dataTypeOf :: HsForAllTelescope GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcTc -> HsForAllTelescope GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) Source # | |||||||||||||
Data (HsLinearArrowTokens GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLinearArrowTokens GhcPs -> c (HsLinearArrowTokens GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLinearArrowTokens GhcPs) Source # toConstr :: HsLinearArrowTokens GhcPs -> Constr Source # dataTypeOf :: HsLinearArrowTokens GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLinearArrowTokens GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLinearArrowTokens GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLinearArrowTokens GhcPs -> HsLinearArrowTokens GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLinearArrowTokens GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLinearArrowTokens GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLinearArrowTokens GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLinearArrowTokens GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcPs -> m (HsLinearArrowTokens GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcPs -> m (HsLinearArrowTokens GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcPs -> m (HsLinearArrowTokens GhcPs) Source # | |||||||||||||
Data (HsLinearArrowTokens GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLinearArrowTokens GhcRn -> c (HsLinearArrowTokens GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLinearArrowTokens GhcRn) Source # toConstr :: HsLinearArrowTokens GhcRn -> Constr Source # dataTypeOf :: HsLinearArrowTokens GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLinearArrowTokens GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLinearArrowTokens GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLinearArrowTokens GhcRn -> HsLinearArrowTokens GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLinearArrowTokens GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLinearArrowTokens GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLinearArrowTokens GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLinearArrowTokens GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcRn -> m (HsLinearArrowTokens GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcRn -> m (HsLinearArrowTokens GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcRn -> m (HsLinearArrowTokens GhcRn) Source # | |||||||||||||
Data (HsLinearArrowTokens GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLinearArrowTokens GhcTc -> c (HsLinearArrowTokens GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLinearArrowTokens GhcTc) Source # toConstr :: HsLinearArrowTokens GhcTc -> Constr Source # dataTypeOf :: HsLinearArrowTokens GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLinearArrowTokens GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLinearArrowTokens GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLinearArrowTokens GhcTc -> HsLinearArrowTokens GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLinearArrowTokens GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLinearArrowTokens GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLinearArrowTokens GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLinearArrowTokens GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcTc -> m (HsLinearArrowTokens GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcTc -> m (HsLinearArrowTokens GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLinearArrowTokens GhcTc -> m (HsLinearArrowTokens GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcPs) Source # toConstr :: HsPatSigType GhcPs -> Constr Source # dataTypeOf :: HsPatSigType GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcPs -> HsPatSigType GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcRn) Source # toConstr :: HsPatSigType GhcRn -> Constr Source # dataTypeOf :: HsPatSigType GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcRn -> HsPatSigType GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcTc) Source # toConstr :: HsPatSigType GhcTc -> Constr Source # dataTypeOf :: HsPatSigType GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcTc -> HsPatSigType GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcPs) Source # toConstr :: HsSigType GhcPs -> Constr Source # dataTypeOf :: HsSigType GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcPs -> HsSigType GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcRn) Source # toConstr :: HsSigType GhcRn -> Constr Source # dataTypeOf :: HsSigType GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcRn -> HsSigType GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcTc) Source # toConstr :: HsSigType GhcTc -> Constr Source # dataTypeOf :: HsSigType GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcTc -> HsSigType GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) Source # | |||||||||||||
Data (HsTyLit GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit GhcPs -> c (HsTyLit GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyLit GhcPs) Source # toConstr :: HsTyLit GhcPs -> Constr Source # dataTypeOf :: HsTyLit GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyLit GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyLit GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTyLit GhcPs -> HsTyLit GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit GhcPs -> m (HsTyLit GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcPs -> m (HsTyLit GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcPs -> m (HsTyLit GhcPs) Source # | |||||||||||||
Data (HsTyLit GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit GhcRn -> c (HsTyLit GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyLit GhcRn) Source # toConstr :: HsTyLit GhcRn -> Constr Source # dataTypeOf :: HsTyLit GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyLit GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyLit GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTyLit GhcRn -> HsTyLit GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit GhcRn -> m (HsTyLit GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcRn -> m (HsTyLit GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcRn -> m (HsTyLit GhcRn) Source # | |||||||||||||
Data (HsTyLit GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit GhcTc -> c (HsTyLit GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyLit GhcTc) Source # toConstr :: HsTyLit GhcTc -> Constr Source # dataTypeOf :: HsTyLit GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyLit GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyLit GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTyLit GhcTc -> HsTyLit GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit GhcTc -> m (HsTyLit GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcTc -> m (HsTyLit GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcTc -> m (HsTyLit GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcPs) Source # toConstr :: HsType GhcPs -> Constr Source # dataTypeOf :: HsType GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsType GhcPs -> HsType GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcRn) Source # toConstr :: HsType GhcRn -> Constr Source # dataTypeOf :: HsType GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsType GhcRn -> HsType GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source # | |||||||||||||
Data (HsType 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcTc) Source # toConstr :: HsType GhcTc -> Constr Source # dataTypeOf :: HsType GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsType GhcTc -> HsType GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcPs) Source # toConstr :: LHsQTyVars GhcPs -> Constr Source # dataTypeOf :: LHsQTyVars GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcPs -> LHsQTyVars GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcRn) Source # toConstr :: LHsQTyVars GhcRn -> Constr Source # dataTypeOf :: LHsQTyVars GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcRn -> LHsQTyVars GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source # | |||||||||||||
Data (LHsQTyVars 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcTc) Source # toConstr :: LHsQTyVars GhcTc -> Constr Source # dataTypeOf :: LHsQTyVars GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcTc -> LHsQTyVars GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source # | |||||||||||||
IsPass p => CollectPass (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Utils collectXXPat :: CollectFlag (GhcPass p) -> XXPat (GhcPass p) -> [IdP (GhcPass p)] -> [IdP (GhcPass p)] Source # collectXXHsBindsLR :: XXHsBindsLR (GhcPass p) pR -> [IdP (GhcPass p)] -> [IdP (GhcPass p)] Source # collectXSplicePat :: CollectFlag (GhcPass p) -> XSplicePat (GhcPass p) -> [IdP (GhcPass p)] -> [IdP (GhcPass p)] Source # | |||||||||||||
DisambECP (PatBuilder GhcPs) Source # | |||||||||||||
Defined in GHC.Parser.PostProcess
ecpFromCmd' :: LHsCmd GhcPs -> PV (LocatedA (PatBuilder GhcPs)) Source # ecpFromExp' :: LHsExpr GhcPs -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsProjUpdatePV :: SrcSpan -> Located [LocatedAn NoEpAnns (DotFieldOcc 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 -> LHsToken "let" GhcPs -> HsLocalBinds GhcPs -> LHsToken "in" GhcPs -> LocatedA (PatBuilder GhcPs) -> 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 -> LamCaseVariant -> 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) -> LHsToken "@" GhcPs -> 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 -> LHsToken "(" GhcPs -> LocatedA (PatBuilder GhcPs) -> LHsToken ")" GhcPs -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (PatBuilder GhcPs)) Source # mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (PatBuilder GhcPs)) Source # mkHsOverLitPV :: LocatedAn a (HsOverLit GhcPs) -> PV (LocatedAn a (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 (HsUntypedSplice 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 -> LHsToken "@" GhcPs -> LocatedA (PatBuilder GhcPs) -> 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 # | |||||||||||||
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 [LocatedAn NoEpAnns (DotFieldOcc 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 -> LHsToken "let" GhcPs -> HsLocalBinds GhcPs -> LHsToken "in" GhcPs -> LocatedA (HsCmd GhcPs) -> 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 -> LamCaseVariant -> 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) -> LHsToken "@" GhcPs -> 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 -> LHsToken "(" GhcPs -> LocatedA (HsCmd GhcPs) -> LHsToken ")" GhcPs -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (HsCmd GhcPs)) Source # mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsCmd GhcPs)) Source # mkHsOverLitPV :: LocatedAn a (HsOverLit GhcPs) -> PV (LocatedAn a (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 (HsUntypedSplice 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 -> LHsToken "@" GhcPs -> LocatedA (HsCmd GhcPs) -> 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 (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 [LocatedAn NoEpAnns (DotFieldOcc 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 -> LHsToken "let" GhcPs -> HsLocalBinds GhcPs -> LHsToken "in" GhcPs -> LocatedA (HsExpr GhcPs) -> 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 -> LamCaseVariant -> 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) -> LHsToken "@" GhcPs -> 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 -> LHsToken "(" GhcPs -> LocatedA (HsExpr GhcPs) -> LHsToken ")" GhcPs -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (HsExpr GhcPs)) Source # mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsExpr GhcPs)) Source # mkHsOverLitPV :: LocatedAn a (HsOverLit GhcPs) -> PV (LocatedAn a (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 (HsUntypedSplice 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 -> LHsToken "@" GhcPs -> LocatedA (HsExpr GhcPs) -> 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 # | |||||||||||||
DisambInfixOp (HsExpr GhcPs) Source # | |||||||||||||
Defined in GHC.Parser.PostProcess | |||||||||||||
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) -> LHsToken "@" GhcPs -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkHsOpTyPV :: PromotionFlag -> LHsType GhcPs -> LocatedN RdrName -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkUnpackednessPV :: Located UnpackednessPragma -> LocatedA (HsType GhcPs) -> PV (LocatedA (HsType GhcPs)) Source # | |||||||||||||
(HasOccName (IdP (GhcPass p)), OutputableBndrId p) => HasOccName (IEWrappedName (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
Outputable (PatBuilder GhcPs) Source # | |||||||||||||
Defined in GHC.Parser.Types | |||||||||||||
OutputableBndrId p => Outputable (HsTypeOrSigType (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Tc.Errors.Types | |||||||||||||
OutputableBndrId a => Outputable (InstInfo (GhcPass a)) Source # | |||||||||||||
Outputable (HsModule GhcPs) Source # | |||||||||||||
OutputableBndrId p => Outputable (FixitySig (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsIPBinds (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (IPBind (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (Sig (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (AnnDecl (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (ClsInstDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (ConDecl (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (DataFamInstDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (DefaultDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (DerivClauseTys (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (DerivDecl (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (DerivStrategy (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (FamilyDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (ForeignDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (ForeignExport (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (ForeignImport (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (FunDep (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsDataDefn (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (HsDecl (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsDerivingClause (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (HsGroup (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (InstDecl (GhcPass p)) Source # | |||||||||||||
OutputableBndr (IdP (GhcPass p)) => Outputable (RoleAnnotDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (RuleBndr (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (RuleDecl (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (RuleDecls (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (SpliceDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (StandaloneKindSig (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (TyClDecl (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (TyClGroup (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (TyFamInstDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
OutputableBndrId p => Outputable (WarnDecl (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (WarnDecls (GhcPass p)) Source # | |||||||||||||
OutputableBndrId idL => Outputable (ApplicativeArg (GhcPass idL)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
OutputableBndrId p => Outputable (ArithSeqInfo (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
OutputableBndrId p => Outputable (HsCmd (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsCmdTop (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsExpr (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsMatchContext (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
Outputable (HsPragE (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsQuote (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsStmtContext (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
OutputableBndrId p => Outputable (IE (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (IEWrappedName (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
(OutputableBndrId p, Outputable (Anno (IE (GhcPass p))), Outputable (ImportDeclPkgQual (GhcPass p))) => Outputable (ImportDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
Outputable (HsLit (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsOverLit (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 (HsForAllTelescope (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
OutputableBndrId p => Outputable (HsPatSigType (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
OutputableBndrId p => Outputable (HsSigType (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsTyLit (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (HsType (GhcPass p)) Source # | |||||||||||||
OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
OutputableBndr (Located (AmbiguousFieldOcc (GhcPass p))) Source # | |||||||||||||
Defined in GHC.Hs.Type pprBndr :: BindingSite -> Located (AmbiguousFieldOcc (GhcPass p)) -> SDoc Source # pprPrefixOcc :: Located (AmbiguousFieldOcc (GhcPass p)) -> SDoc Source # pprInfixOcc :: Located (AmbiguousFieldOcc (GhcPass p)) -> SDoc Source # bndrIsJoin_maybe :: Located (AmbiguousFieldOcc (GhcPass p)) -> Maybe Int Source # | |||||||||||||
OutputableBndrId p => OutputableBndr (IEWrappedName (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp pprBndr :: BindingSite -> IEWrappedName (GhcPass p) -> SDoc Source # pprPrefixOcc :: IEWrappedName (GhcPass p) -> SDoc Source # pprInfixOcc :: IEWrappedName (GhcPass p) -> SDoc Source # bndrIsJoin_maybe :: IEWrappedName (GhcPass p) -> Maybe Int Source # | |||||||||||||
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 # | |||||||||||||
MapXRec (GhcPass p) Source # | |||||||||||||
UnXRec (GhcPass p) Source # | |||||||||||||
Eq (IE GhcPs) Source # | |||||||||||||
Eq (IE GhcRn) Source # | |||||||||||||
Eq (IE GhcTc) Source # | |||||||||||||
Eq (IEWrappedName GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp (==) :: IEWrappedName GhcPs -> IEWrappedName GhcPs -> Bool # (/=) :: IEWrappedName GhcPs -> IEWrappedName GhcPs -> Bool # | |||||||||||||
Eq (IEWrappedName GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp (==) :: IEWrappedName GhcRn -> IEWrappedName GhcRn -> Bool # (/=) :: IEWrappedName GhcRn -> IEWrappedName GhcRn -> Bool # | |||||||||||||
Eq (IEWrappedName GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp (==) :: IEWrappedName GhcTc -> IEWrappedName GhcTc -> Bool # (/=) :: IEWrappedName GhcTc -> IEWrappedName GhcTc -> Bool # | |||||||||||||
Anno a ~ SrcSpanAnn' (EpAnn an) => WrapXRec (GhcPass p) a Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcPs) Source # toConstr :: HsBindLR GhcPs GhcPs -> Constr Source # dataTypeOf :: HsBindLR GhcPs GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcPs -> HsBindLR GhcPs GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcRn) Source # toConstr :: HsBindLR GhcPs GhcRn -> Constr Source # dataTypeOf :: HsBindLR GhcPs GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcRn -> HsBindLR GhcPs GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source # | |||||||||||||
Data (HsBindLR 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcRn GhcRn) Source # toConstr :: HsBindLR GhcRn GhcRn -> Constr Source # dataTypeOf :: HsBindLR GhcRn GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcRn GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcRn GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcRn GhcRn -> HsBindLR GhcRn GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source # | |||||||||||||
Data (HsBindLR 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcTc GhcTc) Source # toConstr :: HsBindLR GhcTc GhcTc -> Constr Source # dataTypeOf :: HsBindLR GhcTc GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcTc GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcTc GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcTc GhcTc -> HsBindLR GhcTc GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcPs) Source # toConstr :: HsLocalBindsLR GhcPs GhcPs -> Constr Source # dataTypeOf :: HsLocalBindsLR GhcPs GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcPs -> HsLocalBindsLR GhcPs GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcRn) Source # toConstr :: HsLocalBindsLR GhcPs GhcRn -> Constr Source # dataTypeOf :: HsLocalBindsLR GhcPs GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcRn -> HsLocalBindsLR GhcPs GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source # | |||||||||||||
Data (HsLocalBindsLR 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcRn GhcRn) Source # toConstr :: HsLocalBindsLR GhcRn GhcRn -> Constr Source # dataTypeOf :: HsLocalBindsLR GhcRn GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcRn GhcRn -> HsLocalBindsLR GhcRn GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source # | |||||||||||||
Data (HsLocalBindsLR 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcTc GhcTc) Source # toConstr :: HsLocalBindsLR GhcTc GhcTc -> Constr Source # dataTypeOf :: HsLocalBindsLR GhcTc GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcTc GhcTc -> HsLocalBindsLR GhcTc GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcPs) Source # toConstr :: HsValBindsLR GhcPs GhcPs -> Constr Source # dataTypeOf :: HsValBindsLR GhcPs GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcPs -> HsValBindsLR GhcPs GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcRn) Source # toConstr :: HsValBindsLR GhcPs GhcRn -> Constr Source # dataTypeOf :: HsValBindsLR GhcPs GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcRn -> HsValBindsLR GhcPs GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source # | |||||||||||||
Data (HsValBindsLR 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcRn GhcRn) Source # toConstr :: HsValBindsLR GhcRn GhcRn -> Constr Source # dataTypeOf :: HsValBindsLR GhcRn GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcRn GhcRn -> HsValBindsLR GhcRn GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source # | |||||||||||||
Data (HsValBindsLR 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcTc GhcTc) Source # toConstr :: HsValBindsLR GhcTc GhcTc -> Constr Source # dataTypeOf :: HsValBindsLR GhcTc GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcTc GhcTc -> HsValBindsLR GhcTc GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcPs) Source # toConstr :: PatSynBind GhcPs GhcPs -> Constr Source # dataTypeOf :: PatSynBind GhcPs GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcPs -> PatSynBind GhcPs GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcRn) Source # toConstr :: PatSynBind GhcPs GhcRn -> Constr Source # dataTypeOf :: PatSynBind GhcPs GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcRn -> PatSynBind GhcPs GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source # | |||||||||||||
Data (PatSynBind 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcRn GhcRn) Source # toConstr :: PatSynBind GhcRn GhcRn -> Constr Source # dataTypeOf :: PatSynBind GhcRn GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcRn GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcRn GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcRn GhcRn -> PatSynBind GhcRn GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source # | |||||||||||||
Data (PatSynBind 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcTc GhcTc) Source # toConstr :: PatSynBind GhcTc GhcTc -> Constr Source # dataTypeOf :: PatSynBind GhcTc GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcTc GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcTc GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcTc GhcTc -> PatSynBind GhcTc GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source # | |||||||||||||
Data 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcPs rhs) Source # toConstr :: FamEqn GhcPs rhs -> Constr Source # dataTypeOf :: FamEqn GhcPs rhs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcPs rhs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcPs rhs)) Source # gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcPs rhs -> FamEqn GhcPs rhs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcPs rhs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcPs rhs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcPs rhs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcPs rhs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcRn rhs) Source # toConstr :: FamEqn GhcRn rhs -> Constr Source # dataTypeOf :: FamEqn GhcRn rhs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcRn rhs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcRn rhs)) Source # gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcRn rhs -> FamEqn GhcRn rhs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcRn rhs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcRn rhs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcRn rhs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcRn rhs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcTc rhs) Source # toConstr :: FamEqn GhcTc rhs -> Constr Source # dataTypeOf :: FamEqn GhcTc rhs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcTc rhs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcTc rhs)) Source # gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcTc rhs -> FamEqn GhcTc rhs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcTc rhs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcTc rhs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcTc rhs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcTc rhs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # toConstr :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source # dataTypeOf :: GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsCmd GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHS GhcPs (LocatedA (HsCmd GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # toConstr :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source # dataTypeOf :: GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs (LocatedA (HsExpr GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHS GhcPs (LocatedA (HsExpr GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # toConstr :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source # dataTypeOf :: GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsCmd GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHS GhcRn (LocatedA (HsCmd GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # toConstr :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source # dataTypeOf :: GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn (LocatedA (HsExpr GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHS GhcRn (LocatedA (HsExpr GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # toConstr :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source # dataTypeOf :: GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsCmd GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHS GhcTc (LocatedA (HsCmd GhcTc))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # toConstr :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source # dataTypeOf :: GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc (LocatedA (HsExpr GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHS GhcTc (LocatedA (HsExpr GhcTc))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # toConstr :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source # dataTypeOf :: GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsCmd GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsCmd GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # toConstr :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source # dataTypeOf :: GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs (LocatedA (HsExpr GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs (LocatedA (HsExpr GhcPs)) -> m (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # toConstr :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source # dataTypeOf :: GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsCmd GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsCmd GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsCmd GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # toConstr :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source # dataTypeOf :: GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn (LocatedA (HsExpr GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn (LocatedA (HsExpr GhcRn)) -> m (GRHSs GhcRn (LocatedA (HsExpr GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source # toConstr :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source # dataTypeOf :: GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsCmd GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsCmd GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsCmd GhcTc))) 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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # toConstr :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source # dataTypeOf :: GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc (LocatedA (HsExpr GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc (LocatedA (HsExpr GhcTc)) -> m (GRHSs GhcTc (LocatedA (HsExpr GhcTc))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # toConstr :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source # dataTypeOf :: Match GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsCmd GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> Match GhcPs (LocatedA (HsCmd GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsCmd GhcPs)) -> m (Match GhcPs (LocatedA (HsCmd GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # toConstr :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source # dataTypeOf :: Match GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs (LocatedA (HsExpr GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> Match GhcPs (LocatedA (HsExpr GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs (LocatedA (HsExpr GhcPs)) -> m (Match GhcPs (LocatedA (HsExpr GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # toConstr :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source # dataTypeOf :: Match GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsCmd GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> Match GhcRn (LocatedA (HsCmd GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsCmd GhcRn)) -> m (Match GhcRn (LocatedA (HsCmd GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # toConstr :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source # dataTypeOf :: Match GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn (LocatedA (HsExpr GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> Match GhcRn (LocatedA (HsExpr GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn (LocatedA (HsExpr GhcRn)) -> m (Match GhcRn (LocatedA (HsExpr GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # toConstr :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source # dataTypeOf :: Match GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsCmd GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> Match GhcTc (LocatedA (HsCmd GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsCmd GhcTc)) -> m (Match GhcTc (LocatedA (HsCmd GhcTc))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # toConstr :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source # dataTypeOf :: Match GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc (LocatedA (HsExpr GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> Match GhcTc (LocatedA (HsExpr GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc (LocatedA (HsExpr GhcTc)) -> m (Match GhcTc (LocatedA (HsExpr GhcTc))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # toConstr :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source # dataTypeOf :: MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsCmd GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsCmd GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsCmd GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # toConstr :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source # dataTypeOf :: MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs (LocatedA (HsExpr GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs)) -> m (MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # toConstr :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source # dataTypeOf :: MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsCmd GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsCmd GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsCmd GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # toConstr :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source # dataTypeOf :: MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn (LocatedA (HsExpr GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn (LocatedA (HsExpr GhcRn)) -> m (MatchGroup GhcRn (LocatedA (HsExpr GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # toConstr :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source # dataTypeOf :: MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsCmd GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsCmd GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsCmd GhcTc))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # toConstr :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source # dataTypeOf :: MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc (LocatedA (HsExpr GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc (LocatedA (HsExpr GhcTc)) -> m (MatchGroup GhcTc (LocatedA (HsExpr GhcTc))) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcPs) Source # toConstr :: ParStmtBlock GhcPs GhcPs -> Constr Source # dataTypeOf :: ParStmtBlock GhcPs GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcPs -> ParStmtBlock GhcPs GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source # | |||||||||||||
Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcRn) Source # toConstr :: ParStmtBlock GhcPs GhcRn -> Constr Source # dataTypeOf :: ParStmtBlock GhcPs GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcRn -> ParStmtBlock GhcPs GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source # | |||||||||||||
Data (ParStmtBlock 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcRn GhcRn) Source # toConstr :: ParStmtBlock GhcRn GhcRn -> Constr Source # dataTypeOf :: ParStmtBlock GhcRn GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcRn GhcRn -> ParStmtBlock GhcRn GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source # | |||||||||||||
Data (ParStmtBlock 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcTc GhcTc) Source # toConstr :: ParStmtBlock GhcTc GhcTc -> Constr Source # dataTypeOf :: ParStmtBlock GhcTc GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcTc GhcTc -> ParStmtBlock GhcTc GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source # | |||||||||||||
Data 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcPs body) Source # toConstr :: HsRecFields GhcPs body -> Constr Source # dataTypeOf :: HsRecFields GhcPs body -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcPs body)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcPs body)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcPs body -> HsRecFields GhcPs body Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source # | |||||||||||||
Data 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcRn body) Source # toConstr :: HsRecFields GhcRn body -> Constr Source # dataTypeOf :: HsRecFields GhcRn body -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcRn body)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcRn body)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcRn body -> HsRecFields GhcRn body Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source # | |||||||||||||
Data body => Data (HsRecFields 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcTc body) Source # toConstr :: HsRecFields GhcTc body -> Constr Source # dataTypeOf :: HsRecFields GhcTc body -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcTc body)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcTc body)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcTc body -> HsRecFields GhcTc body Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source # | |||||||||||||
Data 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcPs) Source # toConstr :: HsOuterTyVarBndrs flag GhcPs -> Constr Source # dataTypeOf :: HsOuterTyVarBndrs flag GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcPs -> HsOuterTyVarBndrs flag GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcRn) Source # toConstr :: HsOuterTyVarBndrs flag GhcRn -> Constr Source # dataTypeOf :: HsOuterTyVarBndrs flag GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcRn -> HsOuterTyVarBndrs flag GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcTc) Source # toConstr :: HsOuterTyVarBndrs flag GhcTc -> Constr Source # dataTypeOf :: HsOuterTyVarBndrs flag GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcTc -> HsOuterTyVarBndrs flag GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcPs thing) Source # toConstr :: HsScaled GhcPs thing -> Constr Source # dataTypeOf :: HsScaled GhcPs thing -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcPs thing)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcPs thing)) Source # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcPs thing -> HsScaled GhcPs thing Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcPs thing -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcPs thing -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcPs thing -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcPs thing -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcRn thing) Source # toConstr :: HsScaled GhcRn thing -> Constr Source # dataTypeOf :: HsScaled GhcRn thing -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcRn thing)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcRn thing)) Source # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcRn thing -> HsScaled GhcRn thing Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcRn thing -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcRn thing -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcRn thing -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcRn thing -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcTc thing) Source # toConstr :: HsScaled GhcTc thing -> Constr Source # dataTypeOf :: HsScaled GhcTc thing -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcTc thing)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcTc thing)) Source # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcTc thing -> HsScaled GhcTc thing Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcTc thing -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcTc thing -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcTc thing -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcTc thing -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcPs) Source # toConstr :: HsTyVarBndr flag GhcPs -> Constr Source # dataTypeOf :: HsTyVarBndr flag GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcPs -> HsTyVarBndr flag GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcRn) Source # toConstr :: HsTyVarBndr flag GhcRn -> Constr Source # dataTypeOf :: HsTyVarBndr flag GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcRn -> HsTyVarBndr flag GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcTc) Source # toConstr :: HsTyVarBndr flag GhcTc -> Constr Source # dataTypeOf :: HsTyVarBndr flag GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcTc -> HsTyVarBndr flag GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) Source # | |||||||||||||
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcPs thing) Source # toConstr :: HsWildCardBndrs GhcPs thing -> Constr Source # dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) Source # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcPs thing -> HsWildCardBndrs GhcPs thing Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source # | |||||||||||||
Data thing => Data (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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcRn thing) Source # toConstr :: HsWildCardBndrs GhcRn thing -> Constr Source # dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) Source # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcRn thing -> HsWildCardBndrs GhcRn thing Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source # | |||||||||||||
Data thing => Data (HsWildCardBndrs 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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcTc thing) Source # toConstr :: HsWildCardBndrs GhcTc thing -> Constr Source # dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) Source # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcTc thing -> HsWildCardBndrs GhcTc thing Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source # | |||||||||||||
NamedThing (HsTyVarBndr flag GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Type getOccName :: HsTyVarBndr flag GhcRn -> OccName Source # | |||||||||||||
Binary a => Binary (WithHsDocIdentifiers a GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Doc | |||||||||||||
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsBindLR (GhcPass pl) (GhcPass pr)) Source # | |||||||||||||
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsLocalBindsLR (GhcPass pl) (GhcPass pr)) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsValBindsLR (GhcPass pl) (GhcPass pr)) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
(OutputableBndrId l, OutputableBndrId r) => Outputable (PatSynBind (GhcPass l) (GhcPass r)) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
(OutputableBndrId pr, Outputable body) => Outputable (Match (GhcPass pr) body) Source # | |||||||||||||
(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 | |||||||||||||
(OutputableBndrFlag flag p, OutputableBndrFlag flag (NoGhcTcPass p), OutputableBndrId p) => Outputable (HsOuterTyVarBndrs flag (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
(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 | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> Constr Source # dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # toConstr :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> Constr Source # dataTypeOf :: StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)))) Source # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs)) -> m (StmtLR GhcPs GhcPs (LocatedA (HsExpr GhcPs))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source # dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsCmd GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # toConstr :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source # dataTypeOf :: StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcPs GhcRn (LocatedA (HsExpr GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> Constr Source # dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsCmd GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # toConstr :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> Constr Source # dataTypeOf :: StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)))) Source # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn)) -> m (StmtLR GhcRn GhcRn (LocatedA (HsExpr GhcRn))) Source # | |||||||||||||
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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source # toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> Constr Source # dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsCmd GhcTc))) 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))) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # toConstr :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> Constr Source # dataTypeOf :: StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)))) Source # gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc)) -> m (StmtLR GhcTc GhcTc (LocatedA (HsExpr GhcTc))) Source # | |||||||||||||
(Data a, Data b) => Data (HsArg GhcPs a b) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsArg GhcPs a b -> c (HsArg GhcPs a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg GhcPs a b) Source # toConstr :: HsArg GhcPs a b -> Constr Source # dataTypeOf :: HsArg GhcPs a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg GhcPs a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg GhcPs a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsArg GhcPs a b -> HsArg GhcPs a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcPs a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcPs a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsArg GhcPs a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg GhcPs a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg GhcPs a b -> m (HsArg GhcPs a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcPs a b -> m (HsArg GhcPs a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcPs a b -> m (HsArg GhcPs a b) Source # | |||||||||||||
(Data a, Data b) => Data (HsArg GhcRn a b) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsArg GhcRn a b -> c (HsArg GhcRn a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg GhcRn a b) Source # toConstr :: HsArg GhcRn a b -> Constr Source # dataTypeOf :: HsArg GhcRn a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg GhcRn a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg GhcRn a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsArg GhcRn a b -> HsArg GhcRn a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcRn a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcRn a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsArg GhcRn a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg GhcRn a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg GhcRn a b -> m (HsArg GhcRn a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcRn a b -> m (HsArg GhcRn a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcRn a b -> m (HsArg GhcRn a b) Source # | |||||||||||||
(Data a, Data b) => Data (HsArg GhcTc a b) Source # | |||||||||||||
Defined in GHC.Hs.Instances gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsArg GhcTc a b -> c (HsArg GhcTc a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg GhcTc a b) Source # toConstr :: HsArg GhcTc a b -> Constr Source # dataTypeOf :: HsArg GhcTc a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg GhcTc a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg GhcTc a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsArg GhcTc a b -> HsArg GhcTc a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcTc a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcTc a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsArg GhcTc a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg GhcTc a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg GhcTc a b -> m (HsArg GhcTc a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcTc a b -> m (HsArg GhcTc a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcTc a b -> m (HsArg GhcTc a b) Source # | |||||||||||||
(OutputableBndrId pl, OutputableBndrId pr, Anno (StmtLR (GhcPass pl) (GhcPass pr) body) ~ SrcSpanAnnA, Outputable body) => Outputable (StmtLR (GhcPass pl) (GhcPass pr) body) Source # | |||||||||||||
(Outputable tm, Outputable ty) => Outputable (HsArg (GhcPass p) tm ty) Source # | This instance is meant for debug-printing purposes. If you wish to
pretty-print an application of | ||||||||||||
data HsRecUpdParent GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
data HsRecUpdParent GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
data HsRecUpdParent GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type ImportDeclPkgQual GhcPs Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type ImportDeclPkgQual GhcRn Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type ImportDeclPkgQual GhcTc Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XAmbiguous GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XAmbiguous GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XAmbiguous GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XAnyClassStrategy GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XAnyClassStrategy GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XAnyClassStrategy GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XAppTypeE GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XAppTypeE GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XAppTypeE GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XApplicativeArgOne GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XApplicativeArgOne GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XApplicativeArgOne GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XArithSeq GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XArithSeq GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XArithSeq GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XAsPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XAsPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XAsPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XBangPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XBangPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XBangPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XCClsInstDecl GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCClsInstDecl GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCClsInstDecl GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCDefaultDecl GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCDefaultDecl GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCDefaultDecl GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCFieldOcc GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XCFieldOcc GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XCFieldOcc GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XCIPBind GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XCIPBind GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XCIPBind GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XCImportDecl GhcPs Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XCImportDecl GhcRn Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XCImportDecl GhcTc Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XCModule GhcPs Source # | |||||||||||||
type XCModule GhcRn Source # | |||||||||||||
Defined in GHC.Hs | |||||||||||||
type XCModule GhcTc Source # | |||||||||||||
Defined in GHC.Hs | |||||||||||||
type XCRoleAnnotDecl GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCRoleAnnotDecl GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCRoleAnnotDecl GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCRuleDecls GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCRuleDecls GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCRuleDecls GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCase GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCase GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCase GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XClassDecl GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XClassDecl GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XClassDecl GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCmdArrApp GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdArrApp GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdArrApp GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdArrForm GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdArrForm GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdArrForm GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdCase GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdCase GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdCase GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdDo GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdDo GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdDo GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdIf GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdIf GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdIf GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdLet GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdLet GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdLet GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdTop GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdTop GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdTop GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XConPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XConPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XConPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XDataDecl GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XDataDecl GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XDataDecl GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XDecBrG GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XDecBrG GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XDecBrG GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XDecBrL GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XDecBrL GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XDecBrL GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XDo GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XDo GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XDo GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExpBr GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExpBr GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExpBr GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitList GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitList GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitList GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitListTy GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XExplicitListTy GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XExplicitListTy GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XExplicitSum GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitSum GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitSum GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitTuple GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitTuple GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitTuple GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExplicitTupleTy GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XExplicitTupleTy GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XExplicitTupleTy GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XExprWithTySig GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExprWithTySig GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XExprWithTySig GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XForeignExport GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XForeignExport GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XForeignExport GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XForeignImport GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XForeignImport GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XForeignImport GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XGetField GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XGetField GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XGetField GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XHsOuterImplicit GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsOuterImplicit GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsOuterImplicit GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsPS GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsPS GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsPS GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsQTvs GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsQTvs GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsQTvs GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsRule GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XHsRule GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XHsRule GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XIEModuleContents GhcPs Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEModuleContents GhcRn Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEModuleContents GhcTc Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingAbs GhcPs Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingAbs GhcRn Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingAbs GhcTc Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingAll GhcPs Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingAll GhcRn Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingAll GhcTc Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingWith GhcPs Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingWith GhcRn Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEThingWith GhcTc Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEVar GhcPs Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEVar GhcRn Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEVar GhcTc Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIPBinds GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XIPBinds GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XIPBinds GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XIPVar GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XIPVar GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XIPVar GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XIf GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XIf GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XIf GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLHsRecUpdLabels GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLHsRecUpdLabels GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLHsRecUpdLabels GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLazyPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XLazyPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XLazyPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XLet GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLet GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLet GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XListPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XListPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XListPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XMissing GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XMissing GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XMissing GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XMultiIf GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XMultiIf GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XMultiIf GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XNPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XNPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XNPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XNPlusKPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XNPlusKPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XNPlusKPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XNegApp GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XNegApp GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XNegApp GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XNewtypeStrategy GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XNewtypeStrategy GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XNewtypeStrategy GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XOpApp GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XOpApp GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XOpApp GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XOverLabel GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XOverLabel GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XOverLabel GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XOverLit GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XOverLit GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XOverLit GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XPatBr GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XPatBr GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XPatBr GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XProjection GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XProjection GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XProjection GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecSel GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecSel GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecSel GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecTy GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XRecTy GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XRecTy GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XRecordCon GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecordCon GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecordCon GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecordUpd GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecordUpd GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecordUpd GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XSectionL GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XSectionL GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XSectionL GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XSectionR GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XSectionR GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XSectionR GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XSigPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSigPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSigPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSplicePat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSplicePat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSplicePat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSpliceTy GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XSpliceTy GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XSpliceTy GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XStandaloneKindSig GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XStandaloneKindSig GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XStandaloneKindSig GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XStatic GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XStatic GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XStatic GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XStockStrategy GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XStockStrategy GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XStockStrategy GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XSumPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSumPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSumPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XSynDecl GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XSynDecl GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XSynDecl GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XTuplePat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XTuplePat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XTuplePat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XTyFamInstD GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XTyFamInstD GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XTyFamInstD GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XTypBr GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTypBr GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTypBr GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTypedBracket GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTypedBracket GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTypedBracket GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTypedSplice GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTypedSplice GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTypedSplice GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUnambiguous GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XUnambiguous GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XUnambiguous GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XUnboundVar GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUnboundVar GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUnboundVar GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedBracket GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedBracket GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedBracket GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedSplice GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedSplice GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedSplice GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedSpliceExpr GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedSpliceExpr GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XUntypedSpliceExpr GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XVarBr GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XVarBr GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XVarBr GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XViaStrategy GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XViaStrategy GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XViaStrategy GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XViewPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XViewPat GhcRn Source # | |||||||||||||
type XViewPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XWarnings GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XWarnings GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XWarnings GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XWildPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XWildPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XWildPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XXCmd GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXCmd GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXCmd GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXExpr GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXExpr GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXExpr GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXPat GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XXPat GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XXPat GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XXQuote GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXQuote GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXQuote GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXSig GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXSig GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXSig GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type ConLikeP GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type ConLikeP GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type ConLikeP GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XHsOuterExplicit GhcPs _1 Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsOuterExplicit GhcRn _1 Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsOuterExplicit GhcTc flag Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsWC GhcPs b Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsWC GhcRn b Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsWC GhcTc b Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XMG GhcPs b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XMG GhcRn b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XMG GhcTc b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXHsBindsLR GhcPs pR Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXHsBindsLR GhcRn pR Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXHsBindsLR GhcTc pR Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XPatBind GhcPs (GhcPass pR) Source # | |||||||||||||
type XPatBind GhcRn (GhcPass pR) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XPatBind GhcTc (GhcPass pR) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type Body (PatBuilder GhcPs) Source # | |||||||||||||
Defined in GHC.Parser.PostProcess | |||||||||||||
type Body (HsCmd GhcPs) Source # | |||||||||||||
Defined in GHC.Parser.PostProcess | |||||||||||||
type Body (HsExpr GhcPs) Source # | |||||||||||||
Defined in GHC.Parser.PostProcess | |||||||||||||
type FunArg (PatBuilder GhcPs) Source # | |||||||||||||
Defined in GHC.Parser.PostProcess | |||||||||||||
type FunArg (HsCmd GhcPs) Source # | |||||||||||||
type FunArg (HsExpr GhcPs) Source # | |||||||||||||
type InfixOp (PatBuilder GhcPs) Source # | |||||||||||||
Defined in GHC.Parser.PostProcess | |||||||||||||
type InfixOp (HsCmd GhcPs) Source # | |||||||||||||
type InfixOp (HsExpr GhcPs) Source # | |||||||||||||
type SyntaxExpr (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type Anno (LocatedA (IE (GhcPass p))) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type Anno (FixitySig (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type Anno (IPBind (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type Anno (Sig (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type Anno (AnnDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (ClsInstDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (ConDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (DataFamInstDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (DefaultDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (DerivClauseTys (GhcPass _1)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (DerivDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (DerivStrategy (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (DocDecl (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 (ForeignDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (FunDep (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (HsDecl (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 (InstDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (RoleAnnotDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (RuleBndr (GhcPass p)) Source # | |||||||||||||
type Anno (RuleDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (RuleDecls (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (SpliceDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (StandaloneKindSig (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (TyClDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type Anno (TyFamInstDecl (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 (DotFieldOcc (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type Anno (FieldLabelStrings (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type Anno (HsCmd (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type Anno (HsCmdTop (GhcPass p)) Source # | |||||||||||||
type Anno (HsExpr (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type Anno (HsUntypedSplice (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type Anno (IE (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type Anno (IEWrappedName (GhcPass _1)) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type Anno (ImportDecl (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type Anno (HsOverLit (GhcPass p)) Source # | |||||||||||||
type Anno (Pat (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type Anno (AmbiguousFieldOcc (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (BangType (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (ConDeclField (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (FieldOcc (GhcPass p)) Source # | |||||||||||||
type Anno (HsKind (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (HsSigType (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (HsType (GhcPass p)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
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 (Match 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 (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 (body (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 (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] Source # | |||||||||||||
Defined in GHC.Parser.Types | |||||||||||||
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 IdP (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Extension | |||||||||||||
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 XAnnD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XApp (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XAppKindTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XAppTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XApplicativeArgMany (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XBangTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XCDerivDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCDotFieldOcc (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCExport (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCFamilyDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCFunDep (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCHsDataDefn (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCHsDerivingClause (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCHsGroup (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCImport (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCInjectivityAnn (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCKindSig (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCRuleBndr (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCTyClGroup (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCTyFamInstDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCharTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XClassOpSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XClsInstD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCmdApp (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCmdLam (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 XCmdWrap (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCompleteMatchSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XConDeclField (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XConDeclGADT (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XConDeclH98 (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XDataFamInstD (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 XDefD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XDerivD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XDocD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XDocTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XFamDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XFixSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XFixitySig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XForAllTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XForD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XFunTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsAnnotation (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XHsChar (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsCharPrim (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 XHsForAllInvis (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsForAllVis (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsInt (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsInt16Prim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsInt32Prim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsInt64Prim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsInt8Prim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsIntPrim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsInteger (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsRat (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsSig (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XHsString (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsStringPrim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsWord16Prim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsWord32Prim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsWord64Prim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsWord8Prim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XHsWordPrim (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XIEDoc (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEDocNamed (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEGroup (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEName (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEPattern (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIEType (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XIParamTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XInlineSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XInstD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XKindSig (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XKindSigD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XKindedTyVar (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XLam (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLam (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLamCase (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XListTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XLitE (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLitPat (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XMinimalSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XNoSig (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XNumTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XOpTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XOverLitE (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XPar (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XParPat (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XParTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XPatSynSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XPragE (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XPresent (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XProc (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XQualTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XRoleAnnotD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XRuleBndrSig (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XRuleD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XSCC (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XSCCFunSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XSigD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XSpecInstSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XSpecSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XSpliceD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XSpliceDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XStarTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XStrTy (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 XTyClD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XTyLit (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XTyVar (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XTyVarSig (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XTypeSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XUserTyVar (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XValD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XVar (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XVar (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XVarPat (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Pat | |||||||||||||
type XWarning (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XWarningD (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XWildCardTy (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXAmbiguousFieldOcc (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXAnnDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXApplicativeArg (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXClsInstDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXCmdTop (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXConDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXConDeclField (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXDefaultDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXDerivClauseTys (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXDerivDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXDotFieldOcc (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXFamilyDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXFamilyResultSig (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXFieldOcc (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXFixitySig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXForeignDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXForeignExport (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXForeignImport (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXFunDep (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXHsDataDefn (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXHsDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXHsDerivingClause (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXHsForAllTelescope (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXHsGroup (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXHsIPBinds (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXHsOuterTyVarBndrs (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 XXIE (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XXIEWrappedName (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XXIPBind (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXImportDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.ImpExp | |||||||||||||
type XXInjectivityAnn (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXInstDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXLHsQTyVars (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXLit (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XXOverLit (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Lit | |||||||||||||
type XXPragE (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXRoleAnnotDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXRuleBndr (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 XXSpliceDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXStandaloneKindSig (GhcPass p) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXTupArg (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXTyClDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXTyClGroup (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXTyFamInstDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXTyLit (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXTyVarBndr (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXType (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXWarnDecl (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXWarnDecls (GhcPass _1) Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCFamEqn (GhcPass _1) r Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XCGRHS (GhcPass _1) _2 Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCGRHSs (GhcPass _1) _2 Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XCMatch (GhcPass _1) b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XFunBind (GhcPass pL) GhcPs Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XFunBind (GhcPass pL) GhcRn Source # | After the renamer (but before the type-checker), the FunBind extension field contains the locally-bound free variables of this defn. See Note [Bind free vars] | ||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XFunBind (GhcPass pL) GhcTc Source # | After the type-checker, the FunBind extension field contains the ticks to put on the rhs, if any, and a coercion from the type of the MatchGroup to the type of the Id. Example: f :: Int -> forall a. a -> a f x y = y Then the MatchGroup will have type (Int -> a' -> a') (with a free type variable a'). The coercion will take a CoreExpr of this type and convert it to a CoreExpr of type Int -> forall a'. a' -> a' Notice that the coercion captures the free a'. | ||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XPSB (GhcPass idL) GhcPs Source # | |||||||||||||
type XPSB (GhcPass idL) GhcRn Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XPSB (GhcPass idL) GhcTc Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XRec (GhcPass p) a Source # | |||||||||||||
Defined in GHC.Hs.Extension | |||||||||||||
type XXFamEqn (GhcPass _1) r Source # | |||||||||||||
Defined in GHC.Hs.Decls | |||||||||||||
type XXGRHS (GhcPass _1) b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXGRHSs (GhcPass _1) _2 Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXHsWildCardBndrs (GhcPass _1) _2 Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type XXMatch (GhcPass _1) b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXMatchGroup (GhcPass _1) b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXValBindsLR (GhcPass pL) pR Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XApplicativeStmt (GhcPass _1) GhcPs b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XApplicativeStmt (GhcPass _1) GhcRn b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XApplicativeStmt (GhcPass _1) GhcTc 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 XBodyStmt (GhcPass _1) GhcPs b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XBodyStmt (GhcPass _1) GhcRn b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XBodyStmt (GhcPass _1) GhcTc b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XParStmt (GhcPass _1) GhcPs b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XParStmt (GhcPass _1) GhcRn b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XParStmt (GhcPass _1) GhcTc b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecStmt (GhcPass _1) GhcPs b Source # | |||||||||||||
type XRecStmt (GhcPass _1) GhcRn b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XRecStmt (GhcPass _1) GhcTc b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTransStmt (GhcPass _1) GhcPs b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTransStmt (GhcPass _1) GhcRn b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XTransStmt (GhcPass _1) GhcTc b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
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 XParStmtBlock (GhcPass pL) (GhcPass pR) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XPatSynBind (GhcPass pL) (GhcPass pR) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XValBinds (GhcPass pL) (GhcPass pR) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XVarBind (GhcPass pL) (GhcPass pR) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XXParStmtBlock (GhcPass pL) (GhcPass pR) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XXPatSynBind (GhcPass idL) (GhcPass idR) Source # | |||||||||||||
Defined in GHC.Hs.Binds | |||||||||||||
type XLastStmt (GhcPass _1) (GhcPass _2) b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type XLetStmt (GhcPass _1) (GhcPass _2) b Source # | |||||||||||||
type XXStmtLR (GhcPass _1) (GhcPass _2) b Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
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 (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) Source # | |||||||||||||
type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) Source # | |||||||||||||
type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) Source # | |||||||||||||
Defined in GHC.Parser.Types | |||||||||||||
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 (Match GhcPs (LocatedA (PatBuilder GhcPs))) Source # | |||||||||||||
Defined in GHC.Parser.Types | |||||||||||||
type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (HsTyVarBndr _flag (GhcPass _1)) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (HsTyVarBndr _flag GhcPs) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (HsTyVarBndr _flag GhcRn) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (HsTyVarBndr _flag GhcTc) Source # | |||||||||||||
Defined in GHC.Hs.Type | |||||||||||||
type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr)))) Source # | |||||||||||||
Defined in GHC.Hs.Expr | |||||||||||||
type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) Source # | |||||||||||||
Defined in GHC.Parser.Types | |||||||||||||
type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pass Source # toConstr :: Pass -> Constr Source # dataTypeOf :: Pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pass) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass) Source # gmapT :: (forall b. Data b => b -> b) -> Pass -> Pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pass -> m Pass Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass Source # |
type GhcTc = GhcPass 'Typechecked Source #
class (NoGhcTcPass (NoGhcTcPass p) ~ NoGhcTcPass p, IsPass (NoGhcTcPass p)) => IsPass (p :: Pass) 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 :: 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].
noHsTok :: forall (tok :: Symbol). GenLocated TokenLocation (HsToken tok) Source #
noHsUniTok :: forall (tok :: Symbol) (utok :: Symbol). GenLocated TokenLocation (HsUniToken tok utok) Source #
Orphan instances
Outputable DataConCantHappen Source # | |
ppr :: DataConCantHappen -> SDoc Source # | |
Outputable NoExtField Source # | |
ppr :: NoExtField -> SDoc Source # | |
KnownSymbol tok => Outputable (HsToken tok) Source # | |
(KnownSymbol tok, KnownSymbol utok) => Outputable (HsUniToken tok utok) Source # | |
ppr :: HsUniToken tok utok -> SDoc Source # |