ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Hs.Extension

Synopsis

Documentation

data NoExtField Source #

A placeholder type for TTG extension points that are not currently unused to represent any particular value.

This should not be confused with NoExtCon, which are found in unused extension constructors and therefore should never be inhabited. In contrast, NoExtField is used in extension points (e.g., as the field of some constructor), so it must have an inhabitant to construct AST passes that manipulate fields with that extension point as their type.

Constructors

NoExtField 

Instances

Instances details
Data NoExtField Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

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

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

toConstr :: NoExtField -> Constr Source #

dataTypeOf :: NoExtField -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable NoExtField Source # 
Instance details

Defined in GHC.Hs.Extension

Eq NoExtField Source # 
Instance details

Defined in GHC.Hs.Extension

Ord NoExtField Source # 
Instance details

Defined in GHC.Hs.Extension

noExtField :: NoExtField Source #

Used when constructing a term with an unused extension point.

data NoExtCon Source #

Used in TTG extension constructors that have yet to be extended with anything. If an extension constructor has NoExtCon as its field, it is not intended to ever be constructed anywhere, and any function that consumes the extension constructor can eliminate it by way of noExtCon.

This should not be confused with NoExtField, which are found in unused extension points (not constructors) and therefore can be inhabited.

Instances

Instances details
Data NoExtCon Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

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

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

toConstr :: NoExtCon -> Constr Source #

dataTypeOf :: NoExtCon -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable NoExtCon Source # 
Instance details

Defined in GHC.Hs.Extension

Eq NoExtCon Source # 
Instance details

Defined in GHC.Hs.Extension

Ord NoExtCon Source # 
Instance details

Defined in GHC.Hs.Extension

noExtCon :: NoExtCon -> a Source #

Eliminate a NoExtCon. Much like absurd.

type family XRec p (f :: Type -> Type) = r | r -> p f Source #

GHC's L prefixed variants wrap their vanilla variant in this type family, to add SrcLoc info via Located. Other passes than GhcPass not interested in location information can define this instance as f p.

Instances

Instances details
type XRec (GhcPass p) f Source # 
Instance details

Defined in GHC.Hs.Extension

type XRec (GhcPass p) f = Located (f (GhcPass p))

data GhcPass (c :: Pass) where Source #

Used as a data type index for the hsSyn AST; also serves as a singleton type for Pass

Constructors

GhcPs :: GhcPs 
GhcRn :: GhcRn 
GhcTc :: GhcTc 

Instances

Instances details
Data (ABExport GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ABExport GhcPs -> Constr Source #

dataTypeOf :: ABExport GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ABExport GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ABExport GhcRn -> Constr Source #

dataTypeOf :: ABExport GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ABExport GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ABExport GhcTc -> Constr Source #

dataTypeOf :: ABExport GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FixitySig GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FixitySig GhcPs -> Constr Source #

dataTypeOf :: FixitySig GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FixitySig GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FixitySig GhcRn -> Constr Source #

dataTypeOf :: FixitySig GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FixitySig GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FixitySig GhcTc -> Constr Source #

dataTypeOf :: FixitySig GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsIPBinds GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsIPBinds GhcPs -> Constr Source #

dataTypeOf :: HsIPBinds GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsIPBinds GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsIPBinds GhcRn -> Constr Source #

dataTypeOf :: HsIPBinds GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsIPBinds GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsIPBinds GhcTc -> Constr Source #

dataTypeOf :: HsIPBinds GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsPatSynDir GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsPatSynDir GhcPs -> Constr Source #

dataTypeOf :: HsPatSynDir GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsPatSynDir GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsPatSynDir GhcRn -> Constr Source #

dataTypeOf :: HsPatSynDir GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsPatSynDir GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsPatSynDir GhcTc -> Constr Source #

dataTypeOf :: HsPatSynDir GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (IPBind GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: IPBind GhcPs -> Constr Source #

dataTypeOf :: IPBind GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (IPBind GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: IPBind GhcRn -> Constr Source #

dataTypeOf :: IPBind GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (IPBind GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: IPBind GhcTc -> Constr Source #

dataTypeOf :: IPBind GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (NHsValBindsLR GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: NHsValBindsLR GhcPs -> Constr Source #

dataTypeOf :: NHsValBindsLR GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (NHsValBindsLR GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: NHsValBindsLR GhcRn -> Constr Source #

dataTypeOf :: NHsValBindsLR GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (NHsValBindsLR GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: NHsValBindsLR GhcTc -> Constr Source #

dataTypeOf :: NHsValBindsLR GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (Sig GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: Sig GhcPs -> Constr Source #

dataTypeOf :: Sig GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (Sig GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: Sig GhcRn -> Constr Source #

dataTypeOf :: Sig GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (Sig GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: Sig GhcTc -> Constr Source #

dataTypeOf :: Sig GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (AnnDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: AnnDecl GhcPs -> Constr Source #

dataTypeOf :: AnnDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (AnnDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: AnnDecl GhcRn -> Constr Source #

dataTypeOf :: AnnDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (AnnDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: AnnDecl GhcTc -> Constr Source #

dataTypeOf :: AnnDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ClsInstDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ClsInstDecl GhcPs -> Constr Source #

dataTypeOf :: ClsInstDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ClsInstDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ClsInstDecl GhcRn -> Constr Source #

dataTypeOf :: ClsInstDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ClsInstDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ClsInstDecl GhcTc -> Constr Source #

dataTypeOf :: ClsInstDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ConDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ConDecl GhcPs -> Constr Source #

dataTypeOf :: ConDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ConDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ConDecl GhcRn -> Constr Source #

dataTypeOf :: ConDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ConDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ConDecl GhcTc -> Constr Source #

dataTypeOf :: ConDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DataFamInstDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DataFamInstDecl GhcPs -> Constr Source #

dataTypeOf :: DataFamInstDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DataFamInstDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DataFamInstDecl GhcRn -> Constr Source #

dataTypeOf :: DataFamInstDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DataFamInstDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DataFamInstDecl GhcTc -> Constr Source #

dataTypeOf :: DataFamInstDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DefaultDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DefaultDecl GhcPs -> Constr Source #

dataTypeOf :: DefaultDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DefaultDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DefaultDecl GhcRn -> Constr Source #

dataTypeOf :: DefaultDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DefaultDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DefaultDecl GhcTc -> Constr Source #

dataTypeOf :: DefaultDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DerivDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DerivDecl GhcPs -> Constr Source #

dataTypeOf :: DerivDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DerivDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DerivDecl GhcRn -> Constr Source #

dataTypeOf :: DerivDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DerivDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DerivDecl GhcTc -> Constr Source #

dataTypeOf :: DerivDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DerivStrategy GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DerivStrategy GhcPs -> Constr Source #

dataTypeOf :: DerivStrategy GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DerivStrategy GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DerivStrategy GhcRn -> Constr Source #

dataTypeOf :: DerivStrategy GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (DerivStrategy GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: DerivStrategy GhcTc -> Constr Source #

dataTypeOf :: DerivStrategy GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyDecl GhcPs -> Constr Source #

dataTypeOf :: FamilyDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyDecl GhcRn -> Constr Source #

dataTypeOf :: FamilyDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyDecl GhcTc -> Constr Source #

dataTypeOf :: FamilyDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyInfo GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyInfo GhcPs -> Constr Source #

dataTypeOf :: FamilyInfo GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyInfo GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyInfo GhcRn -> Constr Source #

dataTypeOf :: FamilyInfo GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyInfo GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyInfo GhcTc -> Constr Source #

dataTypeOf :: FamilyInfo GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyResultSig GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyResultSig GhcPs -> Constr Source #

dataTypeOf :: FamilyResultSig GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyResultSig GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyResultSig GhcRn -> Constr Source #

dataTypeOf :: FamilyResultSig GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (FamilyResultSig GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: FamilyResultSig GhcTc -> Constr Source #

dataTypeOf :: FamilyResultSig GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ForeignDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ForeignDecl GhcPs -> Constr Source #

dataTypeOf :: ForeignDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ForeignDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ForeignDecl GhcRn -> Constr Source #

dataTypeOf :: ForeignDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (ForeignDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: ForeignDecl GhcTc -> Constr Source #

dataTypeOf :: ForeignDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDataDefn GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDataDefn GhcPs -> Constr Source #

dataTypeOf :: HsDataDefn GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDataDefn GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDataDefn GhcRn -> Constr Source #

dataTypeOf :: HsDataDefn GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDataDefn GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDataDefn GhcTc -> Constr Source #

dataTypeOf :: HsDataDefn GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDecl GhcPs -> Constr Source #

dataTypeOf :: HsDecl GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDecl GhcRn -> Constr Source #

dataTypeOf :: HsDecl GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDecl GhcTc -> Constr Source #

dataTypeOf :: HsDecl GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDerivingClause GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDerivingClause GhcPs -> Constr Source #

dataTypeOf :: HsDerivingClause GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDerivingClause GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDerivingClause GhcRn -> Constr Source #

dataTypeOf :: HsDerivingClause GhcRn -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsDerivingClause GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsDerivingClause GhcTc -> Constr Source #

dataTypeOf :: HsDerivingClause GhcTc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsGroup GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsGroup GhcPs -> Constr Source #

dataTypeOf :: HsGroup GhcPs -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data (HsGroup GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

toConstr :: HsGroup GhcRn -> Constr Source #

dataTypeOf :: HsGroup GhcRn -> DataType Source #

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

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

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

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

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

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) Source #

Data (HsGroup GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsGroup GhcTc -> c (HsGroup GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcTc) Source #

toConstr :: HsGroup GhcTc -> Constr Source #

dataTypeOf :: HsGroup GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcTc -> HsGroup GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) Source #

Data (InjectivityAnn GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcPs -> c (InjectivityAnn GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcPs) Source #

toConstr :: InjectivityAnn GhcPs -> Constr Source #

dataTypeOf :: InjectivityAnn GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcPs -> InjectivityAnn GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) Source #

Data (InjectivityAnn GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcRn -> c (InjectivityAnn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcRn) Source #

toConstr :: InjectivityAnn GhcRn -> Constr Source #

dataTypeOf :: InjectivityAnn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcRn -> InjectivityAnn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) Source #

Data (InjectivityAnn GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InjectivityAnn GhcTc -> c (InjectivityAnn GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcTc) Source #

toConstr :: InjectivityAnn GhcTc -> Constr Source #

dataTypeOf :: InjectivityAnn GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcTc -> InjectivityAnn GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) Source #

Data (InstDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcPs -> c (InstDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcPs) Source #

toConstr :: InstDecl GhcPs -> Constr Source #

dataTypeOf :: InstDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcPs -> InstDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) Source #

Data (InstDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcRn -> c (InstDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcRn) Source #

toConstr :: InstDecl GhcRn -> Constr Source #

dataTypeOf :: InstDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcRn -> InstDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) Source #

Data (InstDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstDecl GhcTc -> c (InstDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcTc) Source #

toConstr :: InstDecl GhcTc -> Constr Source #

dataTypeOf :: InstDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcTc -> InstDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) Source #

Data (RoleAnnotDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcPs -> c (RoleAnnotDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcPs) Source #

toConstr :: RoleAnnotDecl GhcPs -> Constr Source #

dataTypeOf :: RoleAnnotDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcPs -> RoleAnnotDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcPs -> m (RoleAnnotDecl GhcPs) Source #

Data (RoleAnnotDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcRn -> c (RoleAnnotDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcRn) Source #

toConstr :: RoleAnnotDecl GhcRn -> Constr Source #

dataTypeOf :: RoleAnnotDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcRn -> RoleAnnotDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcRn -> m (RoleAnnotDecl GhcRn) Source #

Data (RoleAnnotDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RoleAnnotDecl GhcTc -> c (RoleAnnotDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RoleAnnotDecl GhcTc) Source #

toConstr :: RoleAnnotDecl GhcTc -> Constr Source #

dataTypeOf :: RoleAnnotDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RoleAnnotDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RoleAnnotDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> RoleAnnotDecl GhcTc -> RoleAnnotDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RoleAnnotDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RoleAnnotDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RoleAnnotDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RoleAnnotDecl GhcTc -> m (RoleAnnotDecl GhcTc) Source #

Data (RuleBndr GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcPs -> c (RuleBndr GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcPs) Source #

toConstr :: RuleBndr GhcPs -> Constr Source #

dataTypeOf :: RuleBndr GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcPs -> RuleBndr GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) Source #

Data (RuleBndr GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcRn -> c (RuleBndr GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcRn) Source #

toConstr :: RuleBndr GhcRn -> Constr Source #

dataTypeOf :: RuleBndr GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcRn -> RuleBndr GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) Source #

Data (RuleBndr GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleBndr GhcTc -> c (RuleBndr GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcTc) Source #

toConstr :: RuleBndr GhcTc -> Constr Source #

dataTypeOf :: RuleBndr GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcTc -> RuleBndr GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) Source #

Data (RuleDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcPs -> c (RuleDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcPs) Source #

toConstr :: RuleDecl GhcPs -> Constr Source #

dataTypeOf :: RuleDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcPs -> RuleDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) Source #

Data (RuleDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcRn -> c (RuleDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcRn) Source #

toConstr :: RuleDecl GhcRn -> Constr Source #

dataTypeOf :: RuleDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcRn -> RuleDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) Source #

Data (RuleDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecl GhcTc -> c (RuleDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcTc) Source #

toConstr :: RuleDecl GhcTc -> Constr Source #

dataTypeOf :: RuleDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcTc -> RuleDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) Source #

Data (RuleDecls GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcPs -> c (RuleDecls GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcPs) Source #

toConstr :: RuleDecls GhcPs -> Constr Source #

dataTypeOf :: RuleDecls GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcPs -> RuleDecls GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) Source #

Data (RuleDecls GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcRn -> c (RuleDecls GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcRn) Source #

toConstr :: RuleDecls GhcRn -> Constr Source #

dataTypeOf :: RuleDecls GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcRn -> RuleDecls GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) Source #

Data (RuleDecls GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleDecls GhcTc -> c (RuleDecls GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcTc) Source #

toConstr :: RuleDecls GhcTc -> Constr Source #

dataTypeOf :: RuleDecls GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcTc -> RuleDecls GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) Source #

Data (SpliceDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcPs -> c (SpliceDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcPs) Source #

toConstr :: SpliceDecl GhcPs -> Constr Source #

dataTypeOf :: SpliceDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcPs -> SpliceDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) Source #

Data (SpliceDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcRn -> c (SpliceDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcRn) Source #

toConstr :: SpliceDecl GhcRn -> Constr Source #

dataTypeOf :: SpliceDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcRn -> SpliceDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) Source #

Data (SpliceDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceDecl GhcTc -> c (SpliceDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcTc) Source #

toConstr :: SpliceDecl GhcTc -> Constr Source #

dataTypeOf :: SpliceDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcTc -> SpliceDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) Source #

Data (StandaloneKindSig GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcPs -> c (TyClDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcPs) Source #

toConstr :: TyClDecl GhcPs -> Constr Source #

dataTypeOf :: TyClDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcPs -> TyClDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) Source #

Data (TyClDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcRn -> c (TyClDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcRn) Source #

toConstr :: TyClDecl GhcRn -> Constr Source #

dataTypeOf :: TyClDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcRn -> TyClDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) Source #

Data (TyClDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClDecl GhcTc -> c (TyClDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcTc) Source #

toConstr :: TyClDecl GhcTc -> Constr Source #

dataTypeOf :: TyClDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcTc -> TyClDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) Source #

Data (TyClGroup GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcPs -> c (TyClGroup GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcPs) Source #

toConstr :: TyClGroup GhcPs -> Constr Source #

dataTypeOf :: TyClGroup GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcPs -> TyClGroup GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) Source #

Data (TyClGroup GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcRn -> c (TyClGroup GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcRn) Source #

toConstr :: TyClGroup GhcRn -> Constr Source #

dataTypeOf :: TyClGroup GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcRn -> TyClGroup GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) Source #

Data (TyClGroup GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyClGroup GhcTc -> c (TyClGroup GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcTc) Source #

toConstr :: TyClGroup GhcTc -> Constr Source #

dataTypeOf :: TyClGroup GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcTc -> TyClGroup GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) Source #

Data (TyFamInstDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcPs -> c (TyFamInstDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcPs) Source #

toConstr :: TyFamInstDecl GhcPs -> Constr Source #

dataTypeOf :: TyFamInstDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcPs -> TyFamInstDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) Source #

Data (TyFamInstDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcRn -> c (TyFamInstDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcRn) Source #

toConstr :: TyFamInstDecl GhcRn -> Constr Source #

dataTypeOf :: TyFamInstDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcRn -> TyFamInstDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) Source #

Data (TyFamInstDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyFamInstDecl GhcTc -> c (TyFamInstDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcTc) Source #

toConstr :: TyFamInstDecl GhcTc -> Constr Source #

dataTypeOf :: TyFamInstDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcTc -> TyFamInstDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) Source #

Data (WarnDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcPs -> c (WarnDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcPs) Source #

toConstr :: WarnDecl GhcPs -> Constr Source #

dataTypeOf :: WarnDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcPs -> WarnDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) Source #

Data (WarnDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcRn -> c (WarnDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcRn) Source #

toConstr :: WarnDecl GhcRn -> Constr Source #

dataTypeOf :: WarnDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcRn -> WarnDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) Source #

Data (WarnDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecl GhcTc -> c (WarnDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcTc) Source #

toConstr :: WarnDecl GhcTc -> Constr Source #

dataTypeOf :: WarnDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcTc -> WarnDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) Source #

Data (WarnDecls GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcPs -> c (WarnDecls GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcPs) Source #

toConstr :: WarnDecls GhcPs -> Constr Source #

dataTypeOf :: WarnDecls GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcPs -> WarnDecls GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) Source #

Data (WarnDecls GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcRn -> c (WarnDecls GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcRn) Source #

toConstr :: WarnDecls GhcRn -> Constr Source #

dataTypeOf :: WarnDecls GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcRn -> WarnDecls GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) Source #

Data (WarnDecls GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarnDecls GhcTc -> c (WarnDecls GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcTc) Source #

toConstr :: WarnDecls GhcTc -> Constr Source #

dataTypeOf :: WarnDecls GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcTc -> WarnDecls GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) Source #

Data (ApplicativeArg GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcPs -> c (ApplicativeArg GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcPs) Source #

toConstr :: ApplicativeArg GhcPs -> Constr Source #

dataTypeOf :: ApplicativeArg GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcPs -> ApplicativeArg GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) Source #

Data (ApplicativeArg GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcRn -> c (ApplicativeArg GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcRn) Source #

toConstr :: ApplicativeArg GhcRn -> Constr Source #

dataTypeOf :: ApplicativeArg GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcRn -> ApplicativeArg GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) Source #

Data (ApplicativeArg GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ApplicativeArg GhcTc -> c (ApplicativeArg GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcTc) Source #

toConstr :: ApplicativeArg GhcTc -> Constr Source #

dataTypeOf :: ApplicativeArg GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcTc -> ApplicativeArg GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) Source #

Data (ArithSeqInfo GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcPs -> c (ArithSeqInfo GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcPs) Source #

toConstr :: ArithSeqInfo GhcPs -> Constr Source #

dataTypeOf :: ArithSeqInfo GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcPs -> ArithSeqInfo GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) Source #

Data (ArithSeqInfo GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcRn -> c (ArithSeqInfo GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcRn) Source #

toConstr :: ArithSeqInfo GhcRn -> Constr Source #

dataTypeOf :: ArithSeqInfo GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcRn -> ArithSeqInfo GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) Source #

Data (ArithSeqInfo GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArithSeqInfo GhcTc -> c (ArithSeqInfo GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcTc) Source #

toConstr :: ArithSeqInfo GhcTc -> Constr Source #

dataTypeOf :: ArithSeqInfo GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcTc -> ArithSeqInfo GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) Source #

Data (HsBracket GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcPs -> c (HsBracket GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcPs) Source #

toConstr :: HsBracket GhcPs -> Constr Source #

dataTypeOf :: HsBracket GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcPs -> HsBracket GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) Source #

Data (HsBracket GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcRn -> c (HsBracket GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcRn) Source #

toConstr :: HsBracket GhcRn -> Constr Source #

dataTypeOf :: HsBracket GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcRn -> HsBracket GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) Source #

Data (HsBracket GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBracket GhcTc -> c (HsBracket GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcTc) Source #

toConstr :: HsBracket GhcTc -> Constr Source #

dataTypeOf :: HsBracket GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcTc -> HsBracket GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) Source #

Data (HsCmd GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcPs -> c (HsCmd GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcPs) Source #

toConstr :: HsCmd GhcPs -> Constr Source #

dataTypeOf :: HsCmd GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcPs -> HsCmd GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcPs -> m (HsCmd GhcPs) Source #

Data (HsCmd GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcRn -> c (HsCmd GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcRn) Source #

toConstr :: HsCmd GhcRn -> Constr Source #

dataTypeOf :: HsCmd GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcRn -> HsCmd GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcRn -> m (HsCmd GhcRn) Source #

Data (HsCmd GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmd GhcTc -> c (HsCmd GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmd GhcTc) Source #

toConstr :: HsCmd GhcTc -> Constr Source #

dataTypeOf :: HsCmd GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmd GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmd GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmd GhcTc -> HsCmd GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmd GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmd GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmd GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmd GhcTc -> m (HsCmd GhcTc) Source #

Data (HsCmdTop GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcPs -> c (HsCmdTop GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcPs) Source #

toConstr :: HsCmdTop GhcPs -> Constr Source #

dataTypeOf :: HsCmdTop GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcPs -> HsCmdTop GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) Source #

Data (HsCmdTop GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcRn -> c (HsCmdTop GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcRn) Source #

toConstr :: HsCmdTop GhcRn -> Constr Source #

dataTypeOf :: HsCmdTop GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcRn -> HsCmdTop GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) Source #

Data (HsCmdTop GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsCmdTop GhcTc -> c (HsCmdTop GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcTc) Source #

toConstr :: HsCmdTop GhcTc -> Constr Source #

dataTypeOf :: HsCmdTop GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcTc -> HsCmdTop GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) Source #

Data (HsExpr GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcPs -> c (HsExpr GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcPs) Source #

toConstr :: HsExpr GhcPs -> Constr Source #

dataTypeOf :: HsExpr GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcPs -> HsExpr GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcPs -> m (HsExpr GhcPs) Source #

Data (HsExpr GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcRn -> c (HsExpr GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcRn) Source #

toConstr :: HsExpr GhcRn -> Constr Source #

dataTypeOf :: HsExpr GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcRn -> HsExpr GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcRn -> m (HsExpr GhcRn) Source #

Data (HsExpr GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsExpr GhcTc -> c (HsExpr GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsExpr GhcTc) Source #

toConstr :: HsExpr GhcTc -> Constr Source #

dataTypeOf :: HsExpr GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsExpr GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsExpr GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsExpr GhcTc -> HsExpr GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsExpr GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsExpr GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsExpr GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsExpr GhcTc -> m (HsExpr GhcTc) Source #

Data (HsMatchContext GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 (HsSplice GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcPs -> c (HsSplice GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcPs) Source #

toConstr :: HsSplice GhcPs -> Constr Source #

dataTypeOf :: HsSplice GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcPs -> HsSplice GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcPs -> m (HsSplice GhcPs) Source #

Data (HsSplice GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcRn -> c (HsSplice GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcRn) Source #

toConstr :: HsSplice GhcRn -> Constr Source #

dataTypeOf :: HsSplice GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcRn -> HsSplice GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcRn -> m (HsSplice GhcRn) Source #

Data (HsSplice GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplice GhcTc -> c (HsSplice GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplice GhcTc) Source #

toConstr :: HsSplice GhcTc -> Constr Source #

dataTypeOf :: HsSplice GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplice GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplice GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplice GhcTc -> HsSplice GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplice GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplice GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplice GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplice GhcTc -> m (HsSplice GhcTc) Source #

Data (HsSplicedThing GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcPs -> c (HsSplicedThing GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcPs) Source #

toConstr :: HsSplicedThing GhcPs -> Constr Source #

dataTypeOf :: HsSplicedThing GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcPs -> HsSplicedThing GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) Source #

Data (HsSplicedThing GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcRn -> c (HsSplicedThing GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcRn) Source #

toConstr :: HsSplicedThing GhcRn -> Constr Source #

dataTypeOf :: HsSplicedThing GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcRn -> HsSplicedThing GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) Source #

Data (HsSplicedThing GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSplicedThing GhcTc -> c (HsSplicedThing GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcTc) Source #

toConstr :: HsSplicedThing GhcTc -> Constr Source #

dataTypeOf :: HsSplicedThing GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcTc -> HsSplicedThing GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) Source #

Data (HsStmtContext GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcPs -> c (HsTupArg GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcPs) Source #

toConstr :: HsTupArg GhcPs -> Constr Source #

dataTypeOf :: HsTupArg GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcPs -> HsTupArg GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) Source #

Data (HsTupArg GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcRn -> c (HsTupArg GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcRn) Source #

toConstr :: HsTupArg GhcRn -> Constr Source #

dataTypeOf :: HsTupArg GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcRn -> HsTupArg GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) Source #

Data (HsTupArg GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupArg GhcTc -> c (HsTupArg GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcTc) Source #

toConstr :: HsTupArg GhcTc -> Constr Source #

dataTypeOf :: HsTupArg GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcTc -> HsTupArg GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) Source #

Typeable p => Data (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

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 (IE GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcPs -> c (IE GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcPs) Source #

toConstr :: IE GhcPs -> Constr Source #

dataTypeOf :: IE GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcPs -> IE GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcPs -> m (IE GhcPs) Source #

Data (IE GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcRn -> c (IE GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcRn) Source #

toConstr :: IE GhcRn -> Constr Source #

dataTypeOf :: IE GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcRn -> IE GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcRn -> m (IE GhcRn) Source #

Data (IE GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IE GhcTc -> c (IE GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IE GhcTc) Source #

toConstr :: IE GhcTc -> Constr Source #

dataTypeOf :: IE GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IE GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IE GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> IE GhcTc -> IE GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IE GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> IE GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IE GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IE GhcTc -> m (IE GhcTc) Source #

Data (ImportDecl GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcPs -> c (ImportDecl GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcPs) Source #

toConstr :: ImportDecl GhcPs -> Constr Source #

dataTypeOf :: ImportDecl GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcPs -> ImportDecl GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcPs -> m (ImportDecl GhcPs) Source #

Data (ImportDecl GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcRn -> c (ImportDecl GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcRn) Source #

toConstr :: ImportDecl GhcRn -> Constr Source #

dataTypeOf :: ImportDecl GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcRn -> ImportDecl GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcRn -> m (ImportDecl GhcRn) Source #

Data (ImportDecl GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl GhcTc -> c (ImportDecl GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ImportDecl GhcTc) Source #

toConstr :: ImportDecl GhcTc -> Constr Source #

dataTypeOf :: ImportDecl GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ImportDecl GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ImportDecl GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ImportDecl GhcTc -> ImportDecl GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ImportDecl GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl GhcTc -> m (ImportDecl GhcTc) Source #

Data (HsLit GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcPs -> c (HsLit GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcPs) Source #

toConstr :: HsLit GhcPs -> Constr Source #

dataTypeOf :: HsLit GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLit GhcPs -> HsLit GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcPs -> m (HsLit GhcPs) Source #

Data (HsLit GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcRn -> c (HsLit GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcRn) Source #

toConstr :: HsLit GhcRn -> Constr Source #

dataTypeOf :: HsLit GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLit GhcRn -> HsLit GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcRn -> m (HsLit GhcRn) Source #

Data (HsLit GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLit GhcTc -> c (HsLit GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLit GhcTc) Source #

toConstr :: HsLit GhcTc -> Constr Source #

dataTypeOf :: HsLit GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLit GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLit GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLit GhcTc -> HsLit GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLit GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLit GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLit GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLit GhcTc -> m (HsLit GhcTc) Source #

Data (HsOverLit GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcPs -> c (HsOverLit GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcPs) Source #

toConstr :: HsOverLit GhcPs -> Constr Source #

dataTypeOf :: HsOverLit GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcPs -> HsOverLit GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcPs -> m (HsOverLit GhcPs) Source #

Data (HsOverLit GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcRn -> c (HsOverLit GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcRn) Source #

toConstr :: HsOverLit GhcRn -> Constr Source #

dataTypeOf :: HsOverLit GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcRn -> HsOverLit GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcRn -> m (HsOverLit GhcRn) Source #

Data (HsOverLit GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOverLit GhcTc -> c (HsOverLit GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOverLit GhcTc) Source #

toConstr :: HsOverLit GhcTc -> Constr Source #

dataTypeOf :: HsOverLit GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOverLit GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOverLit GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsOverLit GhcTc -> HsOverLit GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOverLit GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsOverLit GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOverLit GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOverLit GhcTc -> m (HsOverLit GhcTc) Source #

Data (Pat GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcPs -> c (Pat GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcPs) Source #

toConstr :: Pat GhcPs -> Constr Source #

dataTypeOf :: Pat GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> Pat GhcPs -> Pat GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Pat GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source #

Data (Pat GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcRn -> c (Pat GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcRn) Source #

toConstr :: Pat GhcRn -> Constr Source #

dataTypeOf :: Pat GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> Pat GhcRn -> Pat GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Pat GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source #

Data (Pat GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcTc -> c (Pat GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcTc) Source #

toConstr :: Pat GhcTc -> Constr Source #

dataTypeOf :: Pat GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> Pat GhcTc -> Pat GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Pat GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source #

Data (AmbiguousFieldOcc GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcPs -> c (AmbiguousFieldOcc GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcPs) Source #

toConstr :: AmbiguousFieldOcc GhcPs -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcPs -> AmbiguousFieldOcc GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcPs -> m (AmbiguousFieldOcc GhcPs) Source #

Data (AmbiguousFieldOcc GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcRn -> c (AmbiguousFieldOcc GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcRn) Source #

toConstr :: AmbiguousFieldOcc GhcRn -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcRn -> AmbiguousFieldOcc GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcRn -> m (AmbiguousFieldOcc GhcRn) Source #

Data (AmbiguousFieldOcc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmbiguousFieldOcc GhcTc -> c (AmbiguousFieldOcc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AmbiguousFieldOcc GhcTc) Source #

toConstr :: AmbiguousFieldOcc GhcTc -> Constr Source #

dataTypeOf :: AmbiguousFieldOcc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AmbiguousFieldOcc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AmbiguousFieldOcc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> AmbiguousFieldOcc GhcTc -> AmbiguousFieldOcc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmbiguousFieldOcc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmbiguousFieldOcc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmbiguousFieldOcc GhcTc -> m (AmbiguousFieldOcc GhcTc) Source #

Data (ConDeclField GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcPs -> c (ConDeclField GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcPs) Source #

toConstr :: ConDeclField GhcPs -> Constr Source #

dataTypeOf :: ConDeclField GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcPs -> ConDeclField GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) Source #

Data (ConDeclField GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcRn -> c (ConDeclField GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcRn) Source #

toConstr :: ConDeclField GhcRn -> Constr Source #

dataTypeOf :: ConDeclField GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcRn -> ConDeclField GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) Source #

Data (ConDeclField GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcTc -> c (ConDeclField GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcTc) Source #

toConstr :: ConDeclField GhcTc -> Constr Source #

dataTypeOf :: ConDeclField GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcTc -> ConDeclField GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) Source #

Data (FieldOcc GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcPs -> c (FieldOcc GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcPs) Source #

toConstr :: FieldOcc GhcPs -> Constr Source #

dataTypeOf :: FieldOcc GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcPs -> FieldOcc GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) Source #

Data (FieldOcc GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcRn -> c (FieldOcc GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcRn) Source #

toConstr :: FieldOcc GhcRn -> Constr Source #

dataTypeOf :: FieldOcc GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcRn -> FieldOcc GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) Source #

Data (FieldOcc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcTc -> c (FieldOcc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcTc) Source #

toConstr :: FieldOcc GhcTc -> Constr Source #

dataTypeOf :: FieldOcc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcTc -> FieldOcc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) Source #

Data (HsArrow GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 (HsForAllTelescope GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 (HsPatSigType GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 (HsType GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcPs -> c (HsType GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcPs) Source #

toConstr :: HsType GhcPs -> Constr Source #

dataTypeOf :: HsType GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsType GhcPs -> HsType GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) Source #

Data (HsType GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcRn -> c (HsType GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcRn) Source #

toConstr :: HsType GhcRn -> Constr Source #

dataTypeOf :: HsType GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsType GhcRn -> HsType GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) Source #

Data (HsType GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcTc -> c (HsType GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcTc) Source #

toConstr :: HsType GhcTc -> Constr Source #

dataTypeOf :: HsType GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsType GhcTc -> HsType GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsType GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) Source #

Data (LHsQTyVars GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcPs -> c (LHsQTyVars GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcPs) Source #

toConstr :: LHsQTyVars GhcPs -> Constr Source #

dataTypeOf :: LHsQTyVars GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcPs -> LHsQTyVars GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) Source #

Data (LHsQTyVars GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcRn -> c (LHsQTyVars GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcRn) Source #

toConstr :: LHsQTyVars GhcRn -> Constr Source #

dataTypeOf :: LHsQTyVars GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcRn -> LHsQTyVars GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) Source #

Data (LHsQTyVars GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcTc -> c (LHsQTyVars GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcTc) Source #

toConstr :: LHsQTyVars GhcTc -> Constr Source #

dataTypeOf :: LHsQTyVars GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcTc -> LHsQTyVars GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) Source #

Data (LHsTypeArg GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsTypeArg GhcPs -> c (LHsTypeArg GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsTypeArg GhcPs) Source #

toConstr :: LHsTypeArg GhcPs -> Constr Source #

dataTypeOf :: LHsTypeArg GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsTypeArg GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsTypeArg GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsTypeArg GhcPs -> LHsTypeArg GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsTypeArg GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsTypeArg GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsTypeArg GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsTypeArg GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcPs -> m (LHsTypeArg GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcPs -> m (LHsTypeArg GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcPs -> m (LHsTypeArg GhcPs) Source #

Data (LHsTypeArg GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsTypeArg GhcRn -> c (LHsTypeArg GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsTypeArg GhcRn) Source #

toConstr :: LHsTypeArg GhcRn -> Constr Source #

dataTypeOf :: LHsTypeArg GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsTypeArg GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsTypeArg GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsTypeArg GhcRn -> LHsTypeArg GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsTypeArg GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsTypeArg GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsTypeArg GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsTypeArg GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcRn -> m (LHsTypeArg GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcRn -> m (LHsTypeArg GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcRn -> m (LHsTypeArg GhcRn) Source #

Data (LHsTypeArg GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsTypeArg GhcTc -> c (LHsTypeArg GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsTypeArg GhcTc) Source #

toConstr :: LHsTypeArg GhcTc -> Constr Source #

dataTypeOf :: LHsTypeArg GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsTypeArg GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsTypeArg GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> LHsTypeArg GhcTc -> LHsTypeArg GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsTypeArg GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsTypeArg GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> LHsTypeArg GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsTypeArg GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcTc -> m (LHsTypeArg GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcTc -> m (LHsTypeArg GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsTypeArg GhcTc -> m (LHsTypeArg GhcTc) Source #

CollectPass (GhcPass 'Parsed) Source # 
Instance details

Defined in GHC.Hs.Utils

CollectPass (GhcPass 'Renamed) Source # 
Instance details

Defined in GHC.Hs.Utils

CollectPass (GhcPass 'Typechecked) Source # 
Instance details

Defined in GHC.Hs.Utils

DisambECP (HsCmd GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

Associated Types

type Body (HsCmd GhcPs) :: Type -> Type Source #

type InfixOp (HsCmd GhcPs) Source #

type FunArg (HsCmd GhcPs) Source #

Methods

ecpFromCmd' :: LHsCmd GhcPs -> PV (Located (HsCmd GhcPs)) Source #

ecpFromExp' :: LHsExpr GhcPs -> PV (Located (HsCmd GhcPs)) Source #

mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located (HsCmd GhcPs)) -> PV (Located (HsCmd GhcPs)) Source #

mkHsLetPV :: SrcSpan -> LHsLocalBinds GhcPs -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

superInfixOp :: (DisambInfixOp (InfixOp (HsCmd GhcPs)) => PV (Located (HsCmd GhcPs))) -> PV (Located (HsCmd GhcPs)) Source #

mkHsOpAppPV :: SrcSpan -> Located (HsCmd GhcPs) -> Located (InfixOp (HsCmd GhcPs)) -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> MatchGroup GhcPs (Located (HsCmd GhcPs)) -> PV (Located (HsCmd GhcPs)) Source #

mkHsLamCasePV :: SrcSpan -> MatchGroup GhcPs (Located (HsCmd GhcPs)) -> PV (Located (HsCmd GhcPs)) Source #

superFunArg :: (DisambECP (FunArg (HsCmd GhcPs)) => PV (Located (HsCmd GhcPs))) -> PV (Located (HsCmd GhcPs)) Source #

mkHsAppPV :: SrcSpan -> Located (HsCmd GhcPs) -> Located (FunArg (HsCmd GhcPs)) -> PV (Located (HsCmd GhcPs)) Source #

mkHsAppTypePV :: SrcSpan -> Located (HsCmd GhcPs) -> LHsType GhcPs -> PV (Located (HsCmd GhcPs)) Source #

mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> Located (HsCmd GhcPs) -> Bool -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsDoPV :: SrcSpan -> Maybe ModuleName -> Located [LStmt GhcPs (Located (HsCmd GhcPs))] -> PV (Located (HsCmd GhcPs)) Source #

mkHsParPV :: SrcSpan -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsVarPV :: Located RdrName -> PV (Located (HsCmd GhcPs)) Source #

mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsWildCardPV :: SrcSpan -> PV (Located (HsCmd GhcPs)) Source #

mkHsTySigPV :: SrcSpan -> Located (HsCmd GhcPs) -> LHsType GhcPs -> PV (Located (HsCmd GhcPs)) Source #

mkHsExplicitListPV :: SrcSpan -> [Located (HsCmd GhcPs)] -> PV (Located (HsCmd GhcPs)) Source #

mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsRecordPV :: SrcSpan -> SrcSpan -> Located (HsCmd GhcPs) -> ([LHsRecField GhcPs (Located (HsCmd GhcPs))], Maybe SrcSpan) -> PV (Located (HsCmd GhcPs)) Source #

mkHsNegAppPV :: SrcSpan -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsSectionR_PV :: SrcSpan -> Located (InfixOp (HsCmd GhcPs)) -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsAsPatPV :: SrcSpan -> Located RdrName -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsLazyPatPV :: SrcSpan -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkHsBangPatPV :: SrcSpan -> Located (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

mkSumOrTuplePV :: SrcSpan -> Boxity -> SumOrTuple (HsCmd GhcPs) -> PV (Located (HsCmd GhcPs)) Source #

rejectPragmaPV :: Located (HsCmd GhcPs) -> PV () Source #

DisambECP (HsExpr GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

Associated Types

type Body (HsExpr GhcPs) :: Type -> Type Source #

type InfixOp (HsExpr GhcPs) Source #

type FunArg (HsExpr GhcPs) Source #

Methods

ecpFromCmd' :: LHsCmd GhcPs -> PV (Located (HsExpr GhcPs)) Source #

ecpFromExp' :: LHsExpr GhcPs -> PV (Located (HsExpr GhcPs)) Source #

mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located (HsExpr GhcPs)) -> PV (Located (HsExpr GhcPs)) Source #

mkHsLetPV :: SrcSpan -> LHsLocalBinds GhcPs -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

superInfixOp :: (DisambInfixOp (InfixOp (HsExpr GhcPs)) => PV (Located (HsExpr GhcPs))) -> PV (Located (HsExpr GhcPs)) Source #

mkHsOpAppPV :: SrcSpan -> Located (HsExpr GhcPs) -> Located (InfixOp (HsExpr GhcPs)) -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> MatchGroup GhcPs (Located (HsExpr GhcPs)) -> PV (Located (HsExpr GhcPs)) Source #

mkHsLamCasePV :: SrcSpan -> MatchGroup GhcPs (Located (HsExpr GhcPs)) -> PV (Located (HsExpr GhcPs)) Source #

superFunArg :: (DisambECP (FunArg (HsExpr GhcPs)) => PV (Located (HsExpr GhcPs))) -> PV (Located (HsExpr GhcPs)) Source #

mkHsAppPV :: SrcSpan -> Located (HsExpr GhcPs) -> Located (FunArg (HsExpr GhcPs)) -> PV (Located (HsExpr GhcPs)) Source #

mkHsAppTypePV :: SrcSpan -> Located (HsExpr GhcPs) -> LHsType GhcPs -> PV (Located (HsExpr GhcPs)) Source #

mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> Located (HsExpr GhcPs) -> Bool -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsDoPV :: SrcSpan -> Maybe ModuleName -> Located [LStmt GhcPs (Located (HsExpr GhcPs))] -> PV (Located (HsExpr GhcPs)) Source #

mkHsParPV :: SrcSpan -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsVarPV :: Located RdrName -> PV (Located (HsExpr GhcPs)) Source #

mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsWildCardPV :: SrcSpan -> PV (Located (HsExpr GhcPs)) Source #

mkHsTySigPV :: SrcSpan -> Located (HsExpr GhcPs) -> LHsType GhcPs -> PV (Located (HsExpr GhcPs)) Source #

mkHsExplicitListPV :: SrcSpan -> [Located (HsExpr GhcPs)] -> PV (Located (HsExpr GhcPs)) Source #

mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsRecordPV :: SrcSpan -> SrcSpan -> Located (HsExpr GhcPs) -> ([LHsRecField GhcPs (Located (HsExpr GhcPs))], Maybe SrcSpan) -> PV (Located (HsExpr GhcPs)) Source #

mkHsNegAppPV :: SrcSpan -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsSectionR_PV :: SrcSpan -> Located (InfixOp (HsExpr GhcPs)) -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsAsPatPV :: SrcSpan -> Located RdrName -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsLazyPatPV :: SrcSpan -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkHsBangPatPV :: SrcSpan -> Located (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

mkSumOrTuplePV :: SrcSpan -> Boxity -> SumOrTuple (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) Source #

rejectPragmaPV :: Located (HsExpr GhcPs) -> PV () Source #

DisambECP (PatBuilder GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

Methods

ecpFromCmd' :: LHsCmd GhcPs -> PV (Located (PatBuilder GhcPs)) Source #

ecpFromExp' :: LHsExpr GhcPs -> PV (Located (PatBuilder GhcPs)) Source #

mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located (PatBuilder GhcPs)) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsLetPV :: SrcSpan -> LHsLocalBinds GhcPs -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

superInfixOp :: (DisambInfixOp (InfixOp (PatBuilder GhcPs)) => PV (Located (PatBuilder GhcPs))) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsOpAppPV :: SrcSpan -> Located (PatBuilder GhcPs) -> Located (InfixOp (PatBuilder GhcPs)) -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> MatchGroup GhcPs (Located (PatBuilder GhcPs)) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsLamCasePV :: SrcSpan -> MatchGroup GhcPs (Located (PatBuilder GhcPs)) -> PV (Located (PatBuilder GhcPs)) Source #

superFunArg :: (DisambECP (FunArg (PatBuilder GhcPs)) => PV (Located (PatBuilder GhcPs))) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsAppPV :: SrcSpan -> Located (PatBuilder GhcPs) -> Located (FunArg (PatBuilder GhcPs)) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsAppTypePV :: SrcSpan -> Located (PatBuilder GhcPs) -> LHsType GhcPs -> PV (Located (PatBuilder GhcPs)) Source #

mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> Located (PatBuilder GhcPs) -> Bool -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsDoPV :: SrcSpan -> Maybe ModuleName -> Located [LStmt GhcPs (Located (PatBuilder GhcPs))] -> PV (Located (PatBuilder GhcPs)) Source #

mkHsParPV :: SrcSpan -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsVarPV :: Located RdrName -> PV (Located (PatBuilder GhcPs)) Source #

mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsOverLitPV :: Located (HsOverLit GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsWildCardPV :: SrcSpan -> PV (Located (PatBuilder GhcPs)) Source #

mkHsTySigPV :: SrcSpan -> Located (PatBuilder GhcPs) -> LHsType GhcPs -> PV (Located (PatBuilder GhcPs)) Source #

mkHsExplicitListPV :: SrcSpan -> [Located (PatBuilder GhcPs)] -> PV (Located (PatBuilder GhcPs)) Source #

mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsRecordPV :: SrcSpan -> SrcSpan -> Located (PatBuilder GhcPs) -> ([LHsRecField GhcPs (Located (PatBuilder GhcPs))], Maybe SrcSpan) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsNegAppPV :: SrcSpan -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsSectionR_PV :: SrcSpan -> Located (InfixOp (PatBuilder GhcPs)) -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsAsPatPV :: SrcSpan -> Located RdrName -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsLazyPatPV :: SrcSpan -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsBangPatPV :: SrcSpan -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkSumOrTuplePV :: SrcSpan -> Boxity -> SumOrTuple (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

rejectPragmaPV :: Located (PatBuilder GhcPs) -> PV () Source #

DisambInfixOp (HsExpr GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

OutputableBndrId p => Outputable (ABExport (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

OutputableBndrId p => Outputable (FixitySig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

OutputableBndrId p => Outputable (HsIPBinds (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

OutputableBndrId p => Outputable (IPBind (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

OutputableBndrId p => Outputable (Sig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: Sig (GhcPass p) -> SDoc Source #

pprPrec :: Rational -> Sig (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (AnnDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (ClsInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (ConDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (DataFamInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (DefaultDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (DerivDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (DerivStrategy (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (FamilyDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (ForeignDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (HsDataDefn (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (HsDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (HsDerivingClause (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (HsGroup (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (InstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndr (IdP (GhcPass p)) => Outputable (RoleAnnotDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (RuleBndr (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (RuleDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (RuleDecls (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (SpliceDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (StandaloneKindSig (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (TyClDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (TyClGroup (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (TyFamInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndr (IdP (GhcPass p)) => Outputable (WarnDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndr (IdP (GhcPass p)) => Outputable (WarnDecls (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId idL => Outputable (ApplicativeArg (GhcPass idL)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (ArithSeqInfo (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsBracket (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsCmd (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsCmdTop (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsExpr (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsMatchContext (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

Outputable (HsPragE (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsSplice (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsSplicedThing (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (HsStmtContext (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId p => Outputable (IE (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Methods

ppr :: IE (GhcPass p) -> SDoc Source #

pprPrec :: Rational -> IE (GhcPass p) -> SDoc Source #

OutputableBndrId p => Outputable (ImportDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.ImpExp

Outputable (HsLit (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Lit

OutputableBndrId p => Outputable (HsOverLit (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Lit

OutputableBndrId p => Outputable (Pat (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: Pat (GhcPass p) -> SDoc Source #

pprPrec :: Rational -> Pat (GhcPass p) -> SDoc Source #

Outputable (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

OutputableBndrId pass => Outputable (HsArrow (GhcPass pass)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsArrow (GhcPass pass) -> SDoc Source #

pprPrec :: Rational -> HsArrow (GhcPass pass) -> SDoc Source #

OutputableBndrId p => Outputable (HsForAllTelescope (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

OutputableBndrId p => Outputable (HsPatSigType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

OutputableBndrId p => Outputable (HsType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Outputable (PatBuilder GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

OutputableBndrId a => Outputable (InstInfo (GhcPass a)) Source # 
Instance details

Defined in GHC.Tc.Utils.Env

OutputableBndr (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Eq (IE GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

(==) :: IE GhcPs -> IE GhcPs -> Bool #

(/=) :: IE GhcPs -> IE GhcPs -> Bool #

Eq (IE GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

(==) :: IE GhcRn -> IE GhcRn -> Bool #

(/=) :: IE GhcRn -> IE GhcRn -> Bool #

Eq (IE GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

(==) :: IE GhcTc -> IE GhcTc -> Bool #

(/=) :: IE GhcTc -> IE GhcTc -> Bool #

Eq (XCFieldOcc (GhcPass p)) => Eq (FieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

(==) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool #

(/=) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool #

Data (HsBindLR GhcPs GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcPs GhcPs -> c (HsBindLR GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcPs) Source #

toConstr :: HsBindLR GhcPs GhcPs -> Constr Source #

dataTypeOf :: HsBindLR GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcPs -> HsBindLR GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) Source #

Data (HsBindLR GhcPs GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcPs GhcRn -> c (HsBindLR GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcRn) Source #

toConstr :: HsBindLR GhcPs GhcRn -> Constr Source #

dataTypeOf :: HsBindLR GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcRn -> HsBindLR GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) Source #

Data (HsBindLR GhcRn GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcRn GhcRn -> c (HsBindLR GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcRn GhcRn) Source #

toConstr :: HsBindLR GhcRn GhcRn -> Constr Source #

dataTypeOf :: HsBindLR GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcRn GhcRn -> HsBindLR GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) Source #

Data (HsBindLR GhcTc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBindLR GhcTc GhcTc -> c (HsBindLR GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcTc GhcTc) Source #

toConstr :: HsBindLR GhcTc GhcTc -> Constr Source #

dataTypeOf :: HsBindLR GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcTc GhcTc -> HsBindLR GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) Source #

Data (HsLocalBindsLR GhcPs GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcPs GhcPs -> c (HsLocalBindsLR GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcPs) Source #

toConstr :: HsLocalBindsLR GhcPs GhcPs -> Constr Source #

dataTypeOf :: HsLocalBindsLR GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcPs -> HsLocalBindsLR GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) Source #

Data (HsLocalBindsLR GhcPs GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcPs GhcRn -> c (HsLocalBindsLR GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcRn) Source #

toConstr :: HsLocalBindsLR GhcPs GhcRn -> Constr Source #

dataTypeOf :: HsLocalBindsLR GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcRn -> HsLocalBindsLR GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) Source #

Data (HsLocalBindsLR GhcRn GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcRn GhcRn -> c (HsLocalBindsLR GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcRn GhcRn) Source #

toConstr :: HsLocalBindsLR GhcRn GhcRn -> Constr Source #

dataTypeOf :: HsLocalBindsLR GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcRn GhcRn -> HsLocalBindsLR GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) Source #

Data (HsLocalBindsLR GhcTc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsLocalBindsLR GhcTc GhcTc -> c (HsLocalBindsLR GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcTc GhcTc) Source #

toConstr :: HsLocalBindsLR GhcTc GhcTc -> Constr Source #

dataTypeOf :: HsLocalBindsLR GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcTc GhcTc -> HsLocalBindsLR GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) Source #

Data (HsValBindsLR GhcPs GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcPs GhcPs -> c (HsValBindsLR GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcPs) Source #

toConstr :: HsValBindsLR GhcPs GhcPs -> Constr Source #

dataTypeOf :: HsValBindsLR GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcPs -> HsValBindsLR GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) Source #

Data (HsValBindsLR GhcPs GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcPs GhcRn -> c (HsValBindsLR GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcRn) Source #

toConstr :: HsValBindsLR GhcPs GhcRn -> Constr Source #

dataTypeOf :: HsValBindsLR GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcRn -> HsValBindsLR GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) Source #

Data (HsValBindsLR GhcRn GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcRn GhcRn -> c (HsValBindsLR GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcRn GhcRn) Source #

toConstr :: HsValBindsLR GhcRn GhcRn -> Constr Source #

dataTypeOf :: HsValBindsLR GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcRn GhcRn -> HsValBindsLR GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) Source #

Data (HsValBindsLR GhcTc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsValBindsLR GhcTc GhcTc -> c (HsValBindsLR GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcTc GhcTc) Source #

toConstr :: HsValBindsLR GhcTc GhcTc -> Constr Source #

dataTypeOf :: HsValBindsLR GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcTc GhcTc -> HsValBindsLR GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) Source #

Data (PatSynBind GhcPs GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcPs GhcPs -> c (PatSynBind GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcPs) Source #

toConstr :: PatSynBind GhcPs GhcPs -> Constr Source #

dataTypeOf :: PatSynBind GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcPs -> PatSynBind GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) Source #

Data (PatSynBind GhcPs GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcPs GhcRn -> c (PatSynBind GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcRn) Source #

toConstr :: PatSynBind GhcPs GhcRn -> Constr Source #

dataTypeOf :: PatSynBind GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcRn -> PatSynBind GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) Source #

Data (PatSynBind GhcRn GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcRn GhcRn -> c (PatSynBind GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcRn GhcRn) Source #

toConstr :: PatSynBind GhcRn GhcRn -> Constr Source #

dataTypeOf :: PatSynBind GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcRn GhcRn -> PatSynBind GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) Source #

Data (PatSynBind GhcTc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynBind GhcTc GhcTc -> c (PatSynBind GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcTc GhcTc) Source #

toConstr :: PatSynBind GhcTc GhcTc -> Constr Source #

dataTypeOf :: PatSynBind GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcTc GhcTc -> PatSynBind GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) Source #

Data rhs => Data (FamEqn GhcPs rhs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 body => Data (GRHS GhcPs body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcPs body -> c (GRHS GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs body) Source #

toConstr :: GRHS GhcPs body -> Constr Source #

dataTypeOf :: GRHS GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs body -> GRHS GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) Source #

Data body => Data (GRHS GhcRn body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcRn body -> c (GRHS GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn body) Source #

toConstr :: GRHS GhcRn body -> Constr Source #

dataTypeOf :: GRHS GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn body -> GRHS GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) Source #

Data body => Data (GRHS GhcTc body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHS GhcTc body -> c (GRHS GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc body) Source #

toConstr :: GRHS GhcTc body -> Constr Source #

dataTypeOf :: GRHS GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc body -> GRHS GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) Source #

Data body => Data (GRHSs GhcPs body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcPs body -> c (GRHSs GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs body) Source #

toConstr :: GRHSs GhcPs body -> Constr Source #

dataTypeOf :: GRHSs GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs body -> GRHSs GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) Source #

Data body => Data (GRHSs GhcRn body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcRn body -> c (GRHSs GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn body) Source #

toConstr :: GRHSs GhcRn body -> Constr Source #

dataTypeOf :: GRHSs GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn body -> GRHSs GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) Source #

Data body => Data (GRHSs GhcTc body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GRHSs GhcTc body -> c (GRHSs GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc body) Source #

toConstr :: GRHSs GhcTc body -> Constr Source #

dataTypeOf :: GRHSs GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc body -> GRHSs GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) Source #

Data body => Data (Match GhcPs body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcPs body -> c (Match GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs body) Source #

toConstr :: Match GhcPs body -> Constr Source #

dataTypeOf :: Match GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs body -> Match GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) Source #

Data body => Data (Match GhcRn body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcRn body -> c (Match GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn body) Source #

toConstr :: Match GhcRn body -> Constr Source #

dataTypeOf :: Match GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn body -> Match GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) Source #

Data body => Data (Match GhcTc body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match GhcTc body -> c (Match GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc body) Source #

toConstr :: Match GhcTc body -> Constr Source #

dataTypeOf :: Match GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc body -> Match GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) Source #

Data body => Data (MatchGroup GhcPs body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcPs body -> c (MatchGroup GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs body) Source #

toConstr :: MatchGroup GhcPs body -> Constr Source #

dataTypeOf :: MatchGroup GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs body -> MatchGroup GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) Source #

Data body => Data (MatchGroup GhcRn body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcRn body -> c (MatchGroup GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn body) Source #

toConstr :: MatchGroup GhcRn body -> Constr Source #

dataTypeOf :: MatchGroup GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn body -> MatchGroup GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) Source #

Data body => Data (MatchGroup GhcTc body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MatchGroup GhcTc body -> c (MatchGroup GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc body) Source #

toConstr :: MatchGroup GhcTc body -> Constr Source #

dataTypeOf :: MatchGroup GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc body -> MatchGroup GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) Source #

Data (ParStmtBlock GhcPs GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcPs GhcPs -> c (ParStmtBlock GhcPs GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcPs) Source #

toConstr :: ParStmtBlock GhcPs GhcPs -> Constr Source #

dataTypeOf :: ParStmtBlock GhcPs GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcPs -> ParStmtBlock GhcPs GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) Source #

Data (ParStmtBlock GhcPs GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcPs GhcRn -> c (ParStmtBlock GhcPs GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcRn) Source #

toConstr :: ParStmtBlock GhcPs GhcRn -> Constr Source #

dataTypeOf :: ParStmtBlock GhcPs GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcRn -> ParStmtBlock GhcPs GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) Source #

Data (ParStmtBlock GhcRn GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcRn GhcRn -> c (ParStmtBlock GhcRn GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcRn GhcRn) Source #

toConstr :: ParStmtBlock GhcRn GhcRn -> Constr Source #

dataTypeOf :: ParStmtBlock GhcRn GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcRn GhcRn -> ParStmtBlock GhcRn GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) Source #

Data (ParStmtBlock GhcTc GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParStmtBlock GhcTc GhcTc -> c (ParStmtBlock GhcTc GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcTc GhcTc) Source #

toConstr :: ParStmtBlock GhcTc GhcTc -> Constr Source #

dataTypeOf :: ParStmtBlock GhcTc GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcTc GhcTc -> ParStmtBlock GhcTc GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) Source #

Data body => Data (HsRecFields GhcPs body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcPs body -> c (HsRecFields GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcPs body) Source #

toConstr :: HsRecFields GhcPs body -> Constr Source #

dataTypeOf :: HsRecFields GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcPs body -> HsRecFields GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source #

Data body => Data (HsRecFields GhcRn body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcRn body -> c (HsRecFields GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcRn body) Source #

toConstr :: HsRecFields GhcRn body -> Constr Source #

dataTypeOf :: HsRecFields GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcRn body -> HsRecFields GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source #

Data body => Data (HsRecFields GhcTc body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcTc body -> c (HsRecFields GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcTc body) Source #

toConstr :: HsRecFields GhcTc body -> Constr Source #

dataTypeOf :: HsRecFields GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcTc body -> HsRecFields GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source #

Data thing => Data (HsImplicitBndrs GhcPs thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplicitBndrs GhcPs thing -> c (HsImplicitBndrs GhcPs thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcPs thing) Source #

toConstr :: HsImplicitBndrs GhcPs thing -> Constr Source #

dataTypeOf :: HsImplicitBndrs GhcPs thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcPs thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcPs thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcPs thing -> HsImplicitBndrs GhcPs thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcPs thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcPs thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcPs thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcPs thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) Source #

Data thing => Data (HsImplicitBndrs GhcRn thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplicitBndrs GhcRn thing -> c (HsImplicitBndrs GhcRn thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcRn thing) Source #

toConstr :: HsImplicitBndrs GhcRn thing -> Constr Source #

dataTypeOf :: HsImplicitBndrs GhcRn thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcRn thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcRn thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcRn thing -> HsImplicitBndrs GhcRn thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcRn thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcRn thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcRn thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcRn thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) Source #

Data thing => Data (HsImplicitBndrs GhcTc thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplicitBndrs GhcTc thing -> c (HsImplicitBndrs GhcTc thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcTc thing) Source #

toConstr :: HsImplicitBndrs GhcTc thing -> Constr Source #

dataTypeOf :: HsImplicitBndrs GhcTc thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcTc thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcTc thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcTc thing -> HsImplicitBndrs GhcTc thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcTc thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcTc thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcTc thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcTc thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) Source #

Data thing => Data (HsScaled GhcPs thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

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 # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcPs thing -> c (HsWildCardBndrs GhcPs thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcPs thing) Source #

toConstr :: HsWildCardBndrs GhcPs thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcPs thing -> HsWildCardBndrs GhcPs thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) Source #

Data thing => Data (HsWildCardBndrs GhcRn thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcRn thing -> c (HsWildCardBndrs GhcRn thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcRn thing) Source #

toConstr :: HsWildCardBndrs GhcRn thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcRn thing -> HsWildCardBndrs GhcRn thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) Source #

Data thing => Data (HsWildCardBndrs GhcTc thing) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcTc thing -> c (HsWildCardBndrs GhcTc thing) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcTc thing) Source #

toConstr :: HsWildCardBndrs GhcTc thing -> Constr Source #

dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcTc thing -> HsWildCardBndrs GhcTc thing Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) Source #

NamedThing (HsTyVarBndr flag GhcRn) Source # 
Instance details

Defined in GHC.Hs.Type

(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsBindLR (GhcPass pl) (GhcPass pr)) Source # 
Instance details

Defined in GHC.Hs.Binds

(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsLocalBindsLR (GhcPass pl) (GhcPass pr)) Source # 
Instance details

Defined in GHC.Hs.Binds

(OutputableBndrId pl, OutputableBndrId pr) => Outputable (HsValBindsLR (GhcPass pl) (GhcPass pr)) Source # 
Instance details

Defined in GHC.Hs.Binds

(OutputableBndrId l, OutputableBndrId r, Outputable (XXPatSynBind (GhcPass l) (GhcPass r))) => Outputable (PatSynBind (GhcPass l) (GhcPass r)) Source # 
Instance details

Defined in GHC.Hs.Binds

(OutputableBndrId pr, Outputable body) => Outputable (Match (GhcPass pr) body) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: Match (GhcPass pr) body -> SDoc Source #

pprPrec :: Rational -> Match (GhcPass pr) body -> SDoc Source #

Outputable thing => Outputable (HsImplicitBndrs (GhcPass p) thing) Source # 
Instance details

Defined in GHC.Hs.Type

(OutputableBndrId p, OutputableBndrFlag flag) => Outputable (HsTyVarBndr flag (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Type

Methods

ppr :: HsTyVarBndr flag (GhcPass p) -> SDoc Source #

pprPrec :: Rational -> HsTyVarBndr flag (GhcPass p) -> SDoc Source #

Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) Source # 
Instance details

Defined in GHC.Hs.Type

Data body => Data (StmtLR GhcPs GhcPs body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcPs body -> c (StmtLR GhcPs GhcPs body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs body) Source #

toConstr :: StmtLR GhcPs GhcPs body -> Constr Source #

dataTypeOf :: StmtLR GhcPs GhcPs body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs body)) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs body -> StmtLR GhcPs GhcPs body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) Source #

Data body => Data (StmtLR GhcPs GhcRn body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcPs GhcRn body -> c (StmtLR GhcPs GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn body) Source #

toConstr :: StmtLR GhcPs GhcRn body -> Constr Source #

dataTypeOf :: StmtLR GhcPs GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn body -> StmtLR GhcPs GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) Source #

Data body => Data (StmtLR GhcRn GhcRn body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcRn GhcRn body -> c (StmtLR GhcRn GhcRn body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn body) Source #

toConstr :: StmtLR GhcRn GhcRn body -> Constr Source #

dataTypeOf :: StmtLR GhcRn GhcRn body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn body)) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn body -> StmtLR GhcRn GhcRn body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) Source #

Data body => Data (StmtLR GhcTc GhcTc body) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StmtLR GhcTc GhcTc body -> c (StmtLR GhcTc GhcTc body) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc body) Source #

toConstr :: StmtLR GhcTc GhcTc body -> Constr Source #

dataTypeOf :: StmtLR GhcTc GhcTc body -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc body)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc body)) Source #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc body -> StmtLR GhcTc GhcTc body Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc body -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc body -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc body -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc body -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) Source #

(OutputableBndrId pl, OutputableBndrId pr, Outputable body) => Outputable (StmtLR (GhcPass pl) (GhcPass pr) body) Source # 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: StmtLR (GhcPass pl) (GhcPass pr) body -> SDoc Source #

pprPrec :: Rational -> StmtLR (GhcPass pl) (GhcPass pr) body -> SDoc Source #

type XAmbiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XAmbiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XAmbiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type XAppTypeE GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCFieldOcc GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XCFieldOcc GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XCFieldOcc GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type XClassDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XCmdArrApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XConDeclGADT GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XConDeclGADT GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XConDeclGADT GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XConPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XConPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XConPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XDataDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc = Type
type XExplicitList GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitListTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitListTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitListTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitSum GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitTupleTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitTupleTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitTupleTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type XForeignExport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsPS GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XHsPS GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XHsPS GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type XHsRule GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XIPBinds GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XListPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XMissing GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XNPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XOpApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XOverLit GhcPs Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcRn Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcTc Source # 
Instance details

Defined in GHC.Hs.Lit

type XRecordCon GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XSigPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XSpliceTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XSpliceTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XSpliceTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type XStatic GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XSumPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc = [Type]
type XSynDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XTuplePat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XUnambiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XUnambiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XUnambiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type XViaStrategy GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XViewPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XXCmd GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXCmd GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXCmd GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XXPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XXPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XXPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XXSplice GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXSplice GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXSplice GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type ConLikeP GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type ConLikeP GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type ConLikeP GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XHsIB GhcPs _1 Source # 
Instance details

Defined in GHC.Hs.Type

type XHsIB GhcRn _1 Source # 
Instance details

Defined in GHC.Hs.Type

type XHsIB GhcRn _1 = [Name]
type XHsIB GhcTc _1 Source # 
Instance details

Defined in GHC.Hs.Type

type XHsIB GhcTc _1 = [Name]
type XHsWC GhcPs b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcRn b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcRn b = [Name]
type XHsWC GhcTc b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcTc b = [Name]
type XMG GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XPatBind GhcPs (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPatBind GhcRn (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPatBind GhcTc (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type SyntaxExpr (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Expr

type IdP (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Extension

type IdP (GhcPass p) = IdGhcP p
type XABE (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XAnnD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XApp (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XApp (GhcPass _1) = NoExtField
type XAppKindTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XAppTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XApplicativeArgMany (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XAsPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type XBangPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type XBangTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XBinTick (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XBracket (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCClsInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCDefaultDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCDerivDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCFamilyDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCHsDataDefn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCHsDerivingClause (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCHsGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XCImportDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XCKindSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRoleAnnotDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRuleBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRuleDecls (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCTyClGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XClassOpSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XClsInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCmdApp (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrForm (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdIf (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdLam (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdLamCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdLet (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdPar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdWrap (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCompleteMatchSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XConDeclField (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XConDeclH98 (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XConLikeOut (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCoreAnn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XDataFamInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XDecBrG (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XDecBrL (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XDefD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XDerivD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XDocD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XDocTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XExpBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitTuple (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XExprWithTySig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XFamDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XFixSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XForAllTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XForD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XFunTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XHsAnnotation (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsChar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsCharPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsDoublePrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsFloatPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsForAllInvis (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XHsForAllVis (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XHsInt (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsInt64Prim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsIntPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsInteger (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsRat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsString (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsStringPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsWord64Prim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsWordPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XIEDoc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEDocNamed (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEModuleContents (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingAbs (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingAll (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingWith (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIPVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XIParamTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XIdSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XIf (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XIf (GhcPass _1) = NoExtField
type XInlineSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XKindSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XKindSigD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XKindedTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XLam (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLam (GhcPass _1) = NoExtField
type XLamCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLazyPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type XLet (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLet (GhcPass _1) = NoExtField
type XListTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XLitE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLitPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type XMinimalSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XNegApp (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XNoSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XOpTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XOverLabel (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XOverLitE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPar (GhcPass _1) = NoExtField
type XParPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type XParTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XPatBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPatSynSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPragE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPresent (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XProc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XQualTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XQuasiQuote (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecFld (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XRnBracketOut (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XRoleAnnotD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XRuleBndrSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XRuleD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XSCC (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSCC (GhcPass _1) = NoExtField
type XSCCFunSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XSectionL (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSectionR (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSigD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XSpecInstSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XSpecSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XSpliceD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XSpliceDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XSpliceE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSplicePat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type XSpliced (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type XStarTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XSumTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XTExpBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTcBracketOut (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTick (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTickPragma (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTupleTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XTyClD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XTyFamInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XTyLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XTyVarSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XTypBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTypeSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XTypedSplice (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XUnboundVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XUntypedSplice (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XUserTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XValD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XVar (GhcPass _1) = NoExtField
type XVarBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XVarPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type XWarning (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XWarningD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XWarnings (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XWildCardTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXABExport (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXAmbiguousFieldOcc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXAnnDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXApplicativeArg (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXBracket (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXClsInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXCmdTop (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXConDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXConDeclField (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXDefaultDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXDerivDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXFamilyDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXFamilyResultSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXFieldOcc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXForeignDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsDataDefn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsDerivingClause (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsForAllTelescope (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXHsGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsIPBinds (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXHsPatSigType (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXIE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XXIE (GhcPass _1) = NoExtCon
type XXIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXImportDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XXInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXLHsQTyVars (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XXLit (GhcPass _1) = NoExtCon
type XXOverLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XXPragE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXRoleAnnotDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXRuleBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXRuleDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXRuleDecls (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXSpliceDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXTupArg (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXTyClDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXTyClGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXTyVarBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXType (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type XXWarnDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXWarnDecls (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type Body (HsCmd GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Body (HsExpr GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type Body (PatBuilder GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (HsCmd GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (HsExpr GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (PatBuilder GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (HsCmd GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (HsExpr GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (PatBuilder GhcPs) Source # 
Instance details

Defined in GHC.Parser.PostProcess

type XCFamEqn (GhcPass _1) r Source # 
Instance details

Defined in GHC.Hs.Decls

type XCGRHS (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XCGRHS (GhcPass _1) b = NoExtField
type XCGRHSs (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XCGRHSs (GhcPass _1) b = NoExtField
type XCMatch (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XCMatch (GhcPass _1) b = NoExtField
type XFunBind (GhcPass pL) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn = NameSet
type XPSB (GhcPass idL) GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcTc = NameSet
type XRec (GhcPass p) f Source # 
Instance details

Defined in GHC.Hs.Extension

type XRec (GhcPass p) f = Located (f (GhcPass p))
type XXFamEqn (GhcPass _1) r Source # 
Instance details

Defined in GHC.Hs.Decls

type XXFamEqn (GhcPass _1) r = NoExtCon
type XXGRHS (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHS (GhcPass _1) b = NoExtCon
type XXGRHSs (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHSs (GhcPass _1) b = NoExtCon
type XXHsImplicitBndrs (GhcPass _1) _2 Source # 
Instance details

Defined in GHC.Hs.Type

type XXHsWildCardBndrs (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Type

type XXMatch (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXMatch (GhcPass _1) b = NoExtCon
type XXMatchGroup (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcTc b = Type
type XParStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcTc b = Type
type XRecStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XAbsBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XHsIPBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XHsValBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPatSynBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XValBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XVarBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXHsBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXPatSynBind (GhcPass idL) (GhcPass idR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXValBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XLastStmt (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XLastStmt (GhcPass _1) (GhcPass _2) b = NoExtField
type XLetStmt (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XLetStmt (GhcPass _1) (GhcPass _2) b = NoExtField
type XXStmtLR (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXStmtLR (GhcPass _1) (GhcPass _2) b = NoExtCon

data Pass Source #

Constructors

Parsed 
Renamed 
Typechecked 

Instances

Instances details
Data Pass Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pass -> c Pass Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pass Source #

toConstr :: Pass -> Constr Source #

dataTypeOf :: Pass -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pass) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass) Source #

gmapT :: (forall b. Data b => b -> b) -> Pass -> Pass Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Pass -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pass -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pass -> m Pass Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass Source #

class (NoGhcTcPass (NoGhcTcPass p) ~ NoGhcTcPass p, IsPass (NoGhcTcPass p)) => IsPass p where Source #

Allows us to check what phase we're in at GHC's runtime. For example, this class allows us to write > f :: forall p. IsPass p => HsExpr (GhcPass p) -> blah > f e = case ghcPass @p of > GhcPs -> ... in this RHS we have HsExpr GhcPs... > GhcRn -> ... in this RHS we have HsExpr GhcRn... > GhcTc -> ... in this RHS we have HsExpr GhcTc... which is very useful, for example, when pretty-printing. See Note [IsPass].

Methods

ghcPass :: GhcPass p Source #

Instances

Instances details
IsPass 'Parsed Source # 
Instance details

Defined in GHC.Hs.Extension

IsPass 'Renamed Source # 
Instance details

Defined in GHC.Hs.Extension

IsPass 'Typechecked Source # 
Instance details

Defined in GHC.Hs.Extension

type family IdP p Source #

Maps the "normal" id type for a given pass

Instances

Instances details
type IdP (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Extension

type IdP (GhcPass p) = IdGhcP p

type family IdGhcP pass where ... Source #

Maps the "normal" id type for a given GHC pass

type LIdP p = Located (IdP p) Source #

type family NoGhcTc (p :: Type) where ... Source #

Marks that a field uses the GhcRn variant even when the pass parameter is GhcTc. Useful for storing HsTypes in GHC.Hs.Exprs, say, because HsType GhcTc should never occur. See Note [NoGhcTc]

Equations

NoGhcTc (GhcPass pass) = GhcPass (NoGhcTcPass pass) 
NoGhcTc other = other 

type family NoGhcTcPass (p :: Pass) :: Pass where ... Source #

Equations

NoGhcTcPass 'Typechecked = 'Renamed 
NoGhcTcPass other = other 

type family XHsValBinds x x' Source #

Instances

Instances details
type XHsValBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XHsIPBinds x x' Source #

Instances

Instances details
type XHsIPBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XEmptyLocalBinds x x' Source #

Instances

Instances details
type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsLocalBindsLR x x' Source #

Instances

Instances details
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XValBinds x x' Source #

Instances

Instances details
type XValBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXValBindsLR x x' Source #

Instances

Instances details
type XXValBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XFunBind x x' Source #

Instances

Instances details
type XFunBind (GhcPass pL) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPatBind x x' Source #

Instances

Instances details
type XPatBind GhcPs (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPatBind GhcRn (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPatBind GhcTc (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XVarBind x x' Source #

Instances

Instances details
type XVarBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XAbsBinds x x' Source #

Instances

Instances details
type XAbsBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPatSynBind x x' Source #

Instances

Instances details
type XPatSynBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsBindsLR x x' Source #

Instances

Instances details
type XXHsBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XABE x Source #

Instances

Instances details
type XABE (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXABExport x Source #

Instances

Instances details
type XXABExport (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPSB x x' Source #

Instances

Instances details
type XPSB (GhcPass idL) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn = NameSet
type XPSB (GhcPass idL) GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcTc = NameSet

type family XXPatSynBind x x' Source #

Instances

Instances details
type XXPatSynBind (GhcPass idL) (GhcPass idR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XIPBinds x Source #

Instances

Instances details
type XIPBinds GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsIPBinds x Source #

Instances

Instances details
type XXHsIPBinds (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XCIPBind x Source #

Instances

Instances details
type XCIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXIPBind x Source #

Instances

Instances details
type XXIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XTypeSig x Source #

Instances

Instances details
type XTypeSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPatSynSig x Source #

Instances

Instances details
type XPatSynSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XClassOpSig x Source #

Instances

Instances details
type XClassOpSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XIdSig x Source #

Instances

Instances details
type XIdSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XFixSig x Source #

Instances

Instances details
type XFixSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XInlineSig x Source #

Instances

Instances details
type XInlineSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSpecSig x Source #

Instances

Instances details
type XSpecSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSpecInstSig x Source #

Instances

Instances details
type XSpecInstSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XMinimalSig x Source #

Instances

Instances details
type XMinimalSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSCCFunSig x Source #

Instances

Instances details
type XSCCFunSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XCompleteMatchSig x Source #

Instances

Instances details
type XCompleteMatchSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXSig x Source #

Instances

Instances details
type XXSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XFixitySig x Source #

Instances

Instances details
type XFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXFixitySig x Source #

Instances

Instances details
type XXFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XStandaloneKindSig x Source #

Instances

Instances details
type XStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXStandaloneKindSig x Source #

Instances

Instances details
type XXStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyClD x Source #

Instances

Instances details
type XTyClD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XInstD x Source #

Instances

Instances details
type XInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDerivD x Source #

Instances

Instances details
type XDerivD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XValD x Source #

Instances

Instances details
type XValD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSigD x Source #

Instances

Instances details
type XSigD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XKindSigD x Source #

Instances

Instances details
type XKindSigD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDefD x Source #

Instances

Instances details
type XDefD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XForD x Source #

Instances

Instances details
type XForD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XWarningD x Source #

Instances

Instances details
type XWarningD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XAnnD x Source #

Instances

Instances details
type XAnnD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRuleD x Source #

Instances

Instances details
type XRuleD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSpliceD x Source #

Instances

Instances details
type XSpliceD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDocD x Source #

Instances

Instances details
type XDocD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRoleAnnotD x Source #

Instances

Instances details
type XRoleAnnotD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDecl x Source #

Instances

Instances details
type XXHsDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCHsGroup x Source #

Instances

Instances details
type XCHsGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsGroup x Source #

Instances

Instances details
type XXHsGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSpliceDecl x Source #

Instances

Instances details
type XSpliceDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXSpliceDecl x Source #

Instances

Instances details
type XXSpliceDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XFamDecl x Source #

Instances

Instances details
type XFamDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSynDecl x Source #

Instances

Instances details
type XSynDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDataDecl x Source #

Instances

Instances details
type XDataDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XClassDecl x Source #

Instances

Instances details
type XClassDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXTyClDecl x Source #

Instances

Instances details
type XXTyClDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCTyClGroup x Source #

Instances

Instances details
type XCTyClGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXTyClGroup x Source #

Instances

Instances details
type XXTyClGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XNoSig x Source #

Instances

Instances details
type XNoSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCKindSig x Source #

Instances

Instances details
type XCKindSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyVarSig x Source #

Instances

Instances details
type XTyVarSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFamilyResultSig x Source #

Instances

Instances details
type XXFamilyResultSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCFamilyDecl x Source #

Instances

Instances details
type XCFamilyDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFamilyDecl x Source #

Instances

Instances details
type XXFamilyDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCHsDataDefn x Source #

Instances

Instances details
type XCHsDataDefn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDataDefn x Source #

Instances

Instances details
type XXHsDataDefn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCHsDerivingClause x Source #

Instances

Instances details
type XCHsDerivingClause (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDerivingClause x Source #

Instances

Instances details
type XXHsDerivingClause (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XConDeclGADT x Source #

Instances

Instances details
type XConDeclGADT GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XConDeclGADT GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XConDeclGADT GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XConDeclH98 x Source #

Instances

Instances details
type XConDeclH98 (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXConDecl x Source #

Instances

Instances details
type XXConDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCFamEqn x r Source #

Instances

Instances details
type XCFamEqn (GhcPass _1) r Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFamEqn x r Source #

Instances

Instances details
type XXFamEqn (GhcPass _1) r Source # 
Instance details

Defined in GHC.Hs.Decls

type XXFamEqn (GhcPass _1) r = NoExtCon

type family XCClsInstDecl x Source #

Instances

Instances details
type XCClsInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXClsInstDecl x Source #

Instances

Instances details
type XXClsInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XClsInstD x Source #

Instances

Instances details
type XClsInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDataFamInstD x Source #

Instances

Instances details
type XDataFamInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyFamInstD x Source #

Instances

Instances details
type XTyFamInstD (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXInstDecl x Source #

Instances

Instances details
type XXInstDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCDerivDecl x Source #

Instances

Instances details
type XCDerivDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXDerivDecl x Source #

Instances

Instances details
type XXDerivDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XViaStrategy x Source #

Instances

Instances details
type XViaStrategy GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCDefaultDecl x Source #

Instances

Instances details
type XCDefaultDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXDefaultDecl x Source #

Instances

Instances details
type XXDefaultDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XForeignImport x Source #

Instances

Instances details
type XForeignImport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XForeignExport x Source #

Instances

Instances details
type XForeignExport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXForeignDecl x Source #

Instances

Instances details
type XXForeignDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCRuleDecls x Source #

Instances

Instances details
type XCRuleDecls (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleDecls x Source #

Instances

Instances details
type XXRuleDecls (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XHsRule x Source #

Instances

Instances details
type XHsRule GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleDecl x Source #

Instances

Instances details
type XXRuleDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCRuleBndr x Source #

Instances

Instances details
type XCRuleBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRuleBndrSig x Source #

Instances

Instances details
type XRuleBndrSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleBndr x Source #

Instances

Instances details
type XXRuleBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XWarnings x Source #

Instances

Instances details
type XWarnings (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXWarnDecls x Source #

Instances

Instances details
type XXWarnDecls (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XWarning x Source #

Instances

Instances details
type XWarning (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXWarnDecl x Source #

Instances

Instances details
type XXWarnDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XHsAnnotation x Source #

Instances

Instances details
type XHsAnnotation (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXAnnDecl x Source #

Instances

Instances details
type XXAnnDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCRoleAnnotDecl x Source #

Instances

Instances details
type XCRoleAnnotDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRoleAnnotDecl x Source #

Instances

Instances details
type XXRoleAnnotDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XVar x Source #

Instances

Instances details
type XVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XVar (GhcPass _1) = NoExtField

type family XUnboundVar x Source #

Instances

Instances details
type XUnboundVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XConLikeOut x Source #

Instances

Instances details
type XConLikeOut (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecFld x Source #

Instances

Instances details
type XRecFld (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOverLabel x Source #

Instances

Instances details
type XOverLabel (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XIPVar x Source #

Instances

Instances details
type XIPVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOverLitE x Source #

Instances

Instances details
type XOverLitE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLitE x Source #

Instances

Instances details
type XLitE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLam x Source #

Instances

Instances details
type XLam (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLam (GhcPass _1) = NoExtField

type family XLamCase x Source #

Instances

Instances details
type XLamCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApp x Source #

Instances

Instances details
type XApp (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XApp (GhcPass _1) = NoExtField

type family XAppTypeE x Source #

Instances

Instances details
type XAppTypeE GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOpApp x Source #

Instances

Instances details
type XOpApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XNegApp x Source #

Instances

Instances details
type XNegApp (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XPar x Source #

Instances

Instances details
type XPar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPar (GhcPass _1) = NoExtField

type family XSectionL x Source #

Instances

Instances details
type XSectionL (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSectionR x Source #

Instances

Instances details
type XSectionR (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitTuple x Source #

Instances

Instances details
type XExplicitTuple (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitSum x Source #

Instances

Instances details
type XExplicitSum GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCase x Source #

Instances

Instances details
type XCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XIf x Source #

Instances

Instances details
type XIf (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XIf (GhcPass _1) = NoExtField

type family XMultiIf x Source #

Instances

Instances details
type XMultiIf GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLet x Source #

Instances

Instances details
type XLet (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLet (GhcPass _1) = NoExtField

type family XDo x Source #

Instances

Instances details
type XDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc = Type

type family XExplicitList x Source #

Instances

Instances details
type XExplicitList GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecordCon x Source #

Instances

Instances details
type XRecordCon GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecordUpd x Source #

Instances

Instances details
type XRecordUpd GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExprWithTySig x Source #

Instances

Instances details
type XExprWithTySig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XArithSeq x Source #

Instances

Instances details
type XArithSeq GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XBracket x Source #

Instances

Instances details
type XBracket (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRnBracketOut x Source #

Instances

Instances details
type XRnBracketOut (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTcBracketOut x Source #

Instances

Instances details
type XTcBracketOut (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSpliceE x Source #

Instances

Instances details
type XSpliceE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XProc x Source #

Instances

Instances details
type XProc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XStatic x Source #

Instances

Instances details
type XStatic GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTick x Source #

Instances

Instances details
type XTick (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XBinTick x Source #

Instances

Instances details
type XBinTick (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XPragE x Source #

Instances

Instances details
type XPragE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXExpr x Source #

Instances

Instances details
type XXExpr GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXExpr GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSCC x Source #

Instances

Instances details
type XSCC (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSCC (GhcPass _1) = NoExtField

type family XCoreAnn x Source #

Instances

Instances details
type XCoreAnn (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTickPragma x Source #

Instances

Instances details
type XTickPragma (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXPragE x Source #

Instances

Instances details
type XXPragE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XUnambiguous x Source #

Instances

Instances details
type XUnambiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XUnambiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XUnambiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XAmbiguous x Source #

Instances

Instances details
type XAmbiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XAmbiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XAmbiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XXAmbiguousFieldOcc x Source #

Instances

Instances details
type XXAmbiguousFieldOcc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XPresent x Source #

Instances

Instances details
type XPresent (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XMissing x Source #

Instances

Instances details
type XMissing GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXTupArg x Source #

Instances

Instances details
type XXTupArg (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTypedSplice x Source #

Instances

Instances details
type XTypedSplice (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XUntypedSplice x Source #

Instances

Instances details
type XUntypedSplice (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XQuasiQuote x Source #

Instances

Instances details
type XQuasiQuote (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSpliced x Source #

Instances

Instances details
type XSpliced (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXSplice x Source #

Instances

Instances details
type XXSplice GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXSplice GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXSplice GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExpBr x Source #

Instances

Instances details
type XExpBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XPatBr x Source #

Instances

Instances details
type XPatBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XDecBrL x Source #

Instances

Instances details
type XDecBrL (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XDecBrG x Source #

Instances

Instances details
type XDecBrG (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTypBr x Source #

Instances

Instances details
type XTypBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XVarBr x Source #

Instances

Instances details
type XVarBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTExpBr x Source #

Instances

Instances details
type XTExpBr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXBracket x Source #

Instances

Instances details
type XXBracket (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdTop x Source #

Instances

Instances details
type XCmdTop GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXCmdTop x Source #

Instances

Instances details
type XXCmdTop (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XMG x b Source #

Instances

Instances details
type XMG GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXMatchGroup x b Source #

Instances

Instances details
type XXMatchGroup (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCMatch x b Source #

Instances

Instances details
type XCMatch (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XCMatch (GhcPass _1) b = NoExtField

type family XXMatch x b Source #

Instances

Instances details
type XXMatch (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXMatch (GhcPass _1) b = NoExtCon

type family XCGRHSs x b Source #

Instances

Instances details
type XCGRHSs (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XCGRHSs (GhcPass _1) b = NoExtField

type family XXGRHSs x b Source #

Instances

Instances details
type XXGRHSs (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHSs (GhcPass _1) b = NoExtCon

type family XCGRHS x b Source #

Instances

Instances details
type XCGRHS (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XCGRHS (GhcPass _1) b = NoExtField

type family XXGRHS x b Source #

Instances

Instances details
type XXGRHS (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHS (GhcPass _1) b = NoExtCon

type family XLastStmt x x' b Source #

Instances

Instances details
type XLastStmt (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XLastStmt (GhcPass _1) (GhcPass _2) b = NoExtField

type family XBindStmt x x' b Source #

Instances

Instances details
type XBindStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeStmt x x' b Source #

Instances

Instances details
type XApplicativeStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XBodyStmt x x' b Source #

Instances

Instances details
type XBodyStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _1) GhcTc b = Type

type family XLetStmt x x' b Source #

Instances

Instances details
type XLetStmt (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XLetStmt (GhcPass _1) (GhcPass _2) b = NoExtField

type family XParStmt x x' b Source #

Instances

Instances details
type XParStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _1) GhcTc b = Type

type family XTransStmt x x' b Source #

Instances

Instances details
type XTransStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecStmt x x' b Source #

Instances

Instances details
type XRecStmt (GhcPass _1) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _1) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _1) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXStmtLR x x' b Source #

Instances

Instances details
type XXStmtLR (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXStmtLR (GhcPass _1) (GhcPass _2) b = NoExtCon

type family XCmdArrApp x Source #

Instances

Instances details
type XCmdArrApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdArrForm x Source #

Instances

Instances details
type XCmdArrForm (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdApp x Source #

Instances

Instances details
type XCmdApp (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLam x Source #

Instances

Instances details
type XCmdLam (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdPar x Source #

Instances

Instances details
type XCmdPar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdCase x Source #

Instances

Instances details
type XCmdCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLamCase x Source #

Instances

Instances details
type XCmdLamCase (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdIf x Source #

Instances

Instances details
type XCmdIf (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLet x Source #

Instances

Instances details
type XCmdLet (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdDo x Source #

Instances

Instances details
type XCmdDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdWrap x Source #

Instances

Instances details
type XCmdWrap (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXCmd x Source #

Instances

Instances details
type XXCmd GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XXCmd GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XXCmd GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XParStmtBlock x x' Source #

Instances

Instances details
type XParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXParStmtBlock x x' Source #

Instances

Instances details
type XXParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeArgOne x Source #

Instances

Instances details
type XApplicativeArgOne GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeArgMany x Source #

Instances

Instances details
type XApplicativeArgMany (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXApplicativeArg x Source #

Instances

Instances details
type XXApplicativeArg (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XHsChar x Source #

Instances

Instances details
type XHsChar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsCharPrim x Source #

Instances

Instances details
type XHsCharPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsString x Source #

Instances

Instances details
type XHsString (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsStringPrim x Source #

Instances

Instances details
type XHsStringPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInt x Source #

Instances

Instances details
type XHsInt (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsIntPrim x Source #

Instances

Instances details
type XHsIntPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsWordPrim x Source #

Instances

Instances details
type XHsWordPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInt64Prim x Source #

Instances

Instances details
type XHsInt64Prim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsWord64Prim x Source #

Instances

Instances details
type XHsWord64Prim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInteger x Source #

Instances

Instances details
type XHsInteger (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsRat x Source #

Instances

Instances details
type XHsRat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsFloatPrim x Source #

Instances

Instances details
type XHsFloatPrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsDoublePrim x Source #

Instances

Instances details
type XHsDoublePrim (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XXLit x Source #

Instances

Instances details
type XXLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type XXLit (GhcPass _1) = NoExtCon

type family XOverLit x Source #

Instances

Instances details
type XOverLit GhcPs Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcRn Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcTc Source # 
Instance details

Defined in GHC.Hs.Lit

type family XXOverLit x Source #

Instances

Instances details
type XXOverLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XWildPat x Source #

Instances

Instances details
type XWildPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XVarPat x Source #

Instances

Instances details
type XVarPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XLazyPat x Source #

Instances

Instances details
type XLazyPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XAsPat x Source #

Instances

Instances details
type XAsPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XParPat x Source #

Instances

Instances details
type XParPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XBangPat x Source #

Instances

Instances details
type XBangPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XListPat x Source #

Instances

Instances details
type XListPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XTuplePat x Source #

Instances

Instances details
type XTuplePat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSumPat x Source #

Instances

Instances details
type XSumPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc = [Type]

type family XConPat x Source #

Instances

Instances details
type XConPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XConPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XConPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XViewPat x Source #

Instances

Instances details
type XViewPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSplicePat x Source #

Instances

Instances details
type XSplicePat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XLitPat x Source #

Instances

Instances details
type XLitPat (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XNPat x Source #

Instances

Instances details
type XNPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XNPlusKPat x Source #

Instances

Instances details
type XNPlusKPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSigPat x Source #

Instances

Instances details
type XSigPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XCoPat x Source #

type family XXPat x Source #

Instances

Instances details
type XXPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XXPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XXPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type family XHsQTvs x Source #

Instances

Instances details
type XHsQTvs GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XHsQTvs GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XXLHsQTyVars x Source #

Instances

Instances details
type XXLHsQTyVars (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsIB x b Source #

Instances

Instances details
type XHsIB GhcPs _1 Source # 
Instance details

Defined in GHC.Hs.Type

type XHsIB GhcRn _1 Source # 
Instance details

Defined in GHC.Hs.Type

type XHsIB GhcRn _1 = [Name]
type XHsIB GhcTc _1 Source # 
Instance details

Defined in GHC.Hs.Type

type XHsIB GhcTc _1 = [Name]

type family XXHsImplicitBndrs x b Source #

Instances

Instances details
type XXHsImplicitBndrs (GhcPass _1) _2 Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsWC x b Source #

Instances

Instances details
type XHsWC GhcPs b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcRn b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcRn b = [Name]
type XHsWC GhcTc b Source # 
Instance details

Defined in GHC.Hs.Type

type XHsWC GhcTc b = [Name]

type family XXHsWildCardBndrs x b Source #

Instances

Instances details
type XXHsWildCardBndrs (GhcPass _1) b Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsPS x Source #

Instances

Instances details
type XHsPS GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XHsPS GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XHsPS GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XXHsPatSigType x Source #

Instances

Instances details
type XXHsPatSigType (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XForAllTy x Source #

Instances

Instances details
type XForAllTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XQualTy x Source #

Instances

Instances details
type XQualTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XTyVar x Source #

Instances

Instances details
type XTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XAppTy x Source #

Instances

Instances details
type XAppTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XAppKindTy x Source #

Instances

Instances details
type XAppKindTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XFunTy x Source #

Instances

Instances details
type XFunTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XListTy x Source #

Instances

Instances details
type XListTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XTupleTy x Source #

Instances

Instances details
type XTupleTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XSumTy x Source #

Instances

Instances details
type XSumTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XOpTy x Source #

Instances

Instances details
type XOpTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XParTy x Source #

Instances

Instances details
type XParTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XIParamTy x Source #

Instances

Instances details
type XIParamTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XStarTy x Source #

Instances

Instances details
type XStarTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XKindSig x Source #

Instances

Instances details
type XKindSig (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XSpliceTy x Source #

Instances

Instances details
type XSpliceTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XSpliceTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XSpliceTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XDocTy x Source #

Instances

Instances details
type XDocTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XBangTy x Source #

Instances

Instances details
type XBangTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XRecTy x Source #

Instances

Instances details
type XRecTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XExplicitListTy x Source #

Instances

Instances details
type XExplicitListTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitListTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitListTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XExplicitTupleTy x Source #

Instances

Instances details
type XExplicitTupleTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitTupleTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XExplicitTupleTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XTyLit x Source #

Instances

Instances details
type XTyLit (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XWildCardTy x Source #

Instances

Instances details
type XWildCardTy (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXType x Source #

Instances

Instances details
type XXType (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsForAllVis x Source #

Instances

Instances details
type XHsForAllVis (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XHsForAllInvis x Source #

Instances

Instances details
type XHsForAllInvis (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXHsForAllTelescope x Source #

Instances

Instances details
type XXHsForAllTelescope (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XUserTyVar x Source #

Instances

Instances details
type XUserTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XKindedTyVar x Source #

Instances

Instances details
type XKindedTyVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXTyVarBndr x Source #

Instances

Instances details
type XXTyVarBndr (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XConDeclField x Source #

Instances

Instances details
type XConDeclField (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XXConDeclField x Source #

Instances

Instances details
type XXConDeclField (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XCFieldOcc x Source #

Instances

Instances details
type XCFieldOcc GhcPs Source # 
Instance details

Defined in GHC.Hs.Type

type XCFieldOcc GhcRn Source # 
Instance details

Defined in GHC.Hs.Type

type XCFieldOcc GhcTc Source # 
Instance details

Defined in GHC.Hs.Type

type family XXFieldOcc x Source #

Instances

Instances details
type XXFieldOcc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.Type

type family XCImportDecl x Source #

Instances

Instances details
type XCImportDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XXImportDecl x Source #

Instances

Instances details
type XXImportDecl (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEVar x Source #

Instances

Instances details
type XIEVar (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingAbs x Source #

Instances

Instances details
type XIEThingAbs (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingAll x Source #

Instances

Instances details
type XIEThingAll (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingWith x Source #

Instances

Instances details
type XIEThingWith (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEModuleContents x Source #

Instances

Instances details
type XIEModuleContents (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEGroup x Source #

Instances

Instances details
type XIEGroup (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEDoc x Source #

Instances

Instances details
type XIEDoc (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEDocNamed x Source #

Instances

Instances details
type XIEDocNamed (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XXIE x Source #

Instances

Instances details
type XXIE (GhcPass _1) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XXIE (GhcPass _1) = NoExtCon

type OutputableBndrId pass = (OutputableBndr (IdGhcP pass), OutputableBndr (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].

pprIfPs :: forall p. IsPass p => (p ~ 'Parsed => SDoc) -> SDoc Source #

pprIfRn :: forall p. IsPass p => (p ~ 'Renamed => SDoc) -> SDoc Source #

pprIfTc :: forall p. IsPass p => (p ~ 'Typechecked => SDoc) -> SDoc Source #