ghc-lib-parser-8.10.1.20200412: The GHC API, decoupled from GHC versions

Safe HaskellNone
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
Eq NoExtField Source # 
Instance details

Defined in GHC.Hs.Extension

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 #

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

toConstr :: NoExtField -> Constr #

dataTypeOf :: NoExtField -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NoExtField Source # 
Instance details

Defined in GHC.Hs.Extension

Outputable 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
Eq NoExtCon Source # 
Instance details

Defined in GHC.Hs.Extension

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 #

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

toConstr :: NoExtCon -> Constr #

dataTypeOf :: NoExtCon -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NoExtCon Source # 
Instance details

Defined in GHC.Hs.Extension

Outputable NoExtCon Source # 
Instance details

Defined in GHC.Hs.Extension

noExtCon :: NoExtCon -> a Source #

Eliminate a NoExtCon. Much like absurd.

data GhcPass (c :: Pass) Source #

Used as a data type index for the hsSyn AST

Instances
Eq (GhcPass c) Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

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

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

Eq (IE GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

(/=) :: IE GhcTc -> IE GhcTc -> 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 GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

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

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

Eq (XCFieldOcc (GhcPass p)) => Eq (FieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

Methods

(==) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool #

(/=) :: FieldOcc (GhcPass p) -> FieldOcc (GhcPass p) -> Bool #

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

Defined in GHC.Hs.Extension

Methods

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

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

toConstr :: GhcPass c -> Constr #

dataTypeOf :: GhcPass c -> DataType #

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

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

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

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

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

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

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

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

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

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

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) #

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

toConstr :: Pat GhcTc -> Constr #

dataTypeOf :: Pat GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (Pat GhcRn) Source # 
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) #

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

toConstr :: Pat GhcRn -> Constr #

dataTypeOf :: Pat GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (Pat GhcPs) Source # 
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) #

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

toConstr :: Pat GhcPs -> Constr #

dataTypeOf :: Pat GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: IE GhcTc -> Constr #

dataTypeOf :: IE GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (IE GhcRn) Source # 
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) #

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

toConstr :: IE GhcRn -> Constr #

dataTypeOf :: IE GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (IE GhcPs) Source # 
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) #

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

toConstr :: IE GhcPs -> Constr #

dataTypeOf :: IE GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ImportDecl GhcTc) Source # 
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) #

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

toConstr :: ImportDecl GhcTc -> Constr #

dataTypeOf :: ImportDecl GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ImportDecl GhcRn) Source # 
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) #

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

toConstr :: ImportDecl GhcRn -> Constr #

dataTypeOf :: ImportDecl GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ImportDecl GhcPs) Source # 
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) #

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

toConstr :: ImportDecl GhcPs -> Constr #

dataTypeOf :: ImportDecl GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (SyntaxExpr 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) -> SyntaxExpr GhcTc -> c (SyntaxExpr GhcTc) #

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

toConstr :: SyntaxExpr GhcTc -> Constr #

dataTypeOf :: SyntaxExpr GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (SyntaxExpr 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) -> SyntaxExpr GhcRn -> c (SyntaxExpr GhcRn) #

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

toConstr :: SyntaxExpr GhcRn -> Constr #

dataTypeOf :: SyntaxExpr GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (SyntaxExpr 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) -> SyntaxExpr GhcPs -> c (SyntaxExpr GhcPs) #

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

toConstr :: SyntaxExpr GhcPs -> Constr #

dataTypeOf :: SyntaxExpr GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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) #

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

toConstr :: HsSplice GhcTc -> Constr #

dataTypeOf :: HsSplice GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsSplice GhcRn) Source # 
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) #

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

toConstr :: HsSplice GhcRn -> Constr #

dataTypeOf :: HsSplice GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsSplice GhcPs) Source # 
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) #

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

toConstr :: HsSplice GhcPs -> Constr #

dataTypeOf :: HsSplice GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: HsCmd GhcTc -> Constr #

dataTypeOf :: HsCmd GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsCmd GhcRn) Source # 
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) #

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

toConstr :: HsCmd GhcRn -> Constr #

dataTypeOf :: HsCmd GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsCmd GhcPs) Source # 
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) #

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

toConstr :: HsCmd GhcPs -> Constr #

dataTypeOf :: HsCmd GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: HsExpr GhcTc -> Constr #

dataTypeOf :: HsExpr GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsExpr GhcRn) Source # 
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) #

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

toConstr :: HsExpr GhcRn -> Constr #

dataTypeOf :: HsExpr GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsExpr GhcPs) Source # 
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) #

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

toConstr :: HsExpr GhcPs -> Constr #

dataTypeOf :: HsExpr GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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) #

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

toConstr :: HsOverLit GhcTc -> Constr #

dataTypeOf :: HsOverLit GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsOverLit GhcRn) Source # 
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) #

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

toConstr :: HsOverLit GhcRn -> Constr #

dataTypeOf :: HsOverLit GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsOverLit GhcPs) Source # 
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) #

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

toConstr :: HsOverLit GhcPs -> Constr #

dataTypeOf :: HsOverLit GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsLit GhcTc) Source # 
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) #

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

toConstr :: HsLit GhcTc -> Constr #

dataTypeOf :: HsLit GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsLit GhcRn) Source # 
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) #

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

toConstr :: HsLit GhcRn -> Constr #

dataTypeOf :: HsLit GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsLit GhcPs) Source # 
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) #

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

toConstr :: HsLit GhcPs -> Constr #

dataTypeOf :: HsLit GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: AmbiguousFieldOcc GhcTc -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (AmbiguousFieldOcc GhcRn) Source # 
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) #

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

toConstr :: AmbiguousFieldOcc GhcRn -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (AmbiguousFieldOcc GhcPs) Source # 
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) #

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

toConstr :: AmbiguousFieldOcc GhcPs -> Constr #

dataTypeOf :: AmbiguousFieldOcc GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (FieldOcc GhcTc) Source # 
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) #

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

toConstr :: FieldOcc GhcTc -> Constr #

dataTypeOf :: FieldOcc GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (FieldOcc GhcRn) Source # 
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) #

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

toConstr :: FieldOcc GhcRn -> Constr #

dataTypeOf :: FieldOcc GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (FieldOcc GhcPs) Source # 
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) #

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

toConstr :: FieldOcc GhcPs -> Constr #

dataTypeOf :: FieldOcc GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ConDeclField GhcTc) Source # 
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) #

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

toConstr :: ConDeclField GhcTc -> Constr #

dataTypeOf :: ConDeclField GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ConDeclField GhcRn) Source # 
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) #

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

toConstr :: ConDeclField GhcRn -> Constr #

dataTypeOf :: ConDeclField GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ConDeclField GhcPs) Source # 
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) #

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

toConstr :: ConDeclField GhcPs -> Constr #

dataTypeOf :: ConDeclField GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: HsType GhcTc -> Constr #

dataTypeOf :: HsType GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsType GhcRn) Source # 
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) #

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

toConstr :: HsType GhcRn -> Constr #

dataTypeOf :: HsType GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsType GhcPs) Source # 
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) #

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

toConstr :: HsType GhcPs -> Constr #

dataTypeOf :: HsType GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsTyVarBndr 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 GhcTc -> c (HsTyVarBndr GhcTc) #

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

toConstr :: HsTyVarBndr GhcTc -> Constr #

dataTypeOf :: HsTyVarBndr GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsTyVarBndr 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 GhcRn -> c (HsTyVarBndr GhcRn) #

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

toConstr :: HsTyVarBndr GhcRn -> Constr #

dataTypeOf :: HsTyVarBndr GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsTyVarBndr 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 GhcPs -> c (HsTyVarBndr GhcPs) #

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

toConstr :: HsTyVarBndr GhcPs -> Constr #

dataTypeOf :: HsTyVarBndr GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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) #

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

toConstr :: LHsQTyVars GhcTc -> Constr #

dataTypeOf :: LHsQTyVars GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (LHsQTyVars GhcRn) Source # 
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) #

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

toConstr :: LHsQTyVars GhcRn -> Constr #

dataTypeOf :: LHsQTyVars GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (LHsQTyVars GhcPs) Source # 
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) #

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

toConstr :: LHsQTyVars GhcPs -> Constr #

dataTypeOf :: LHsQTyVars GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: HsPatSynDir GhcTc -> Constr #

dataTypeOf :: HsPatSynDir GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsPatSynDir GhcRn) Source # 
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) #

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

toConstr :: HsPatSynDir GhcRn -> Constr #

dataTypeOf :: HsPatSynDir GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsPatSynDir GhcPs) Source # 
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) #

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

toConstr :: HsPatSynDir GhcPs -> Constr #

dataTypeOf :: HsPatSynDir GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: FixitySig GhcTc -> Constr #

dataTypeOf :: FixitySig GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (FixitySig GhcRn) Source # 
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) #

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

toConstr :: FixitySig GhcRn -> Constr #

dataTypeOf :: FixitySig GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (FixitySig GhcPs) Source # 
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) #

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

toConstr :: FixitySig GhcPs -> Constr #

dataTypeOf :: FixitySig GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (Sig GhcTc) Source # 
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) #

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

toConstr :: Sig GhcTc -> Constr #

dataTypeOf :: Sig GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (Sig GhcRn) Source # 
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) #

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

toConstr :: Sig GhcRn -> Constr #

dataTypeOf :: Sig GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (Sig GhcPs) Source # 
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) #

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

toConstr :: Sig GhcPs -> Constr #

dataTypeOf :: Sig GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (IPBind GhcTc) Source # 
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) #

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

toConstr :: IPBind GhcTc -> Constr #

dataTypeOf :: IPBind GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (IPBind GhcRn) Source # 
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) #

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

toConstr :: IPBind GhcRn -> Constr #

dataTypeOf :: IPBind GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (IPBind GhcPs) Source # 
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) #

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

toConstr :: IPBind GhcPs -> Constr #

dataTypeOf :: IPBind GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsIPBinds GhcTc) Source # 
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) #

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

toConstr :: HsIPBinds GhcTc -> Constr #

dataTypeOf :: HsIPBinds GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsIPBinds GhcRn) Source # 
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) #

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

toConstr :: HsIPBinds GhcRn -> Constr #

dataTypeOf :: HsIPBinds GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (HsIPBinds GhcPs) Source # 
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) #

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

toConstr :: HsIPBinds GhcPs -> Constr #

dataTypeOf :: HsIPBinds GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ABExport GhcTc) Source # 
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) #

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

toConstr :: ABExport GhcTc -> Constr #

dataTypeOf :: ABExport GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ABExport GhcRn) Source # 
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) #

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

toConstr :: ABExport GhcRn -> Constr #

dataTypeOf :: ABExport GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (ABExport GhcPs) Source # 
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) #

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

toConstr :: ABExport GhcPs -> Constr #

dataTypeOf :: ABExport GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: NHsValBindsLR GhcTc -> Constr #

dataTypeOf :: NHsValBindsLR GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (NHsValBindsLR GhcRn) Source # 
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) #

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

toConstr :: NHsValBindsLR GhcRn -> Constr #

dataTypeOf :: NHsValBindsLR GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (NHsValBindsLR GhcPs) Source # 
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) #

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

toConstr :: NHsValBindsLR GhcPs -> Constr #

dataTypeOf :: NHsValBindsLR GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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) #

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

toConstr :: RoleAnnotDecl GhcTc -> Constr #

dataTypeOf :: RoleAnnotDecl GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (RoleAnnotDecl GhcRn) Source # 
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) #

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

toConstr :: RoleAnnotDecl GhcRn -> Constr #

dataTypeOf :: RoleAnnotDecl GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (RoleAnnotDecl GhcPs) Source # 
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) #

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

toConstr :: RoleAnnotDecl GhcPs -> Constr #

dataTypeOf :: RoleAnnotDecl GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

Data (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) #

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

toConstr :: AnnDecl GhcTc -> Constr #

dataTypeOf :: AnnDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcTc -> AnnDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcTc -> m (AnnDecl GhcTc) #

Data (AnnDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnDecl GhcRn) #

toConstr :: AnnDecl GhcRn -> Constr #

dataTypeOf :: AnnDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcRn -> AnnDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcRn -> m (AnnDecl GhcRn) #

Data (AnnDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (AnnDecl GhcPs) #

toConstr :: AnnDecl GhcPs -> Constr #

dataTypeOf :: AnnDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (AnnDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (AnnDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> AnnDecl GhcPs -> AnnDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnDecl GhcPs -> m (AnnDecl GhcPs) #

Data (WarnDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcTc) #

toConstr :: WarnDecl GhcTc -> Constr #

dataTypeOf :: WarnDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcTc -> WarnDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcTc -> m (WarnDecl GhcTc) #

Data (WarnDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcRn) #

toConstr :: WarnDecl GhcRn -> Constr #

dataTypeOf :: WarnDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcRn -> WarnDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcRn -> m (WarnDecl GhcRn) #

Data (WarnDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecl GhcPs) #

toConstr :: WarnDecl GhcPs -> Constr #

dataTypeOf :: WarnDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> WarnDecl GhcPs -> WarnDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecl GhcPs -> m (WarnDecl GhcPs) #

Data (WarnDecls GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcTc) #

toConstr :: WarnDecls GhcTc -> Constr #

dataTypeOf :: WarnDecls GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcTc -> WarnDecls GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcTc -> m (WarnDecls GhcTc) #

Data (WarnDecls GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcRn) #

toConstr :: WarnDecls GhcRn -> Constr #

dataTypeOf :: WarnDecls GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcRn -> WarnDecls GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcRn -> m (WarnDecls GhcRn) #

Data (WarnDecls GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WarnDecls GhcPs) #

toConstr :: WarnDecls GhcPs -> Constr #

dataTypeOf :: WarnDecls GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WarnDecls GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WarnDecls GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> WarnDecls GhcPs -> WarnDecls GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarnDecls GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> WarnDecls GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarnDecls GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarnDecls GhcPs -> m (WarnDecls GhcPs) #

Data (RuleBndr GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcTc) #

toConstr :: RuleBndr GhcTc -> Constr #

dataTypeOf :: RuleBndr GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcTc -> RuleBndr GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcTc -> m (RuleBndr GhcTc) #

Data (RuleBndr GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcRn) #

toConstr :: RuleBndr GhcRn -> Constr #

dataTypeOf :: RuleBndr GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcRn -> RuleBndr GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcRn -> m (RuleBndr GhcRn) #

Data (RuleBndr GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleBndr GhcPs) #

toConstr :: RuleBndr GhcPs -> Constr #

dataTypeOf :: RuleBndr GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleBndr GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleBndr GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> RuleBndr GhcPs -> RuleBndr GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleBndr GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleBndr GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleBndr GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleBndr GhcPs -> m (RuleBndr GhcPs) #

Data (RuleDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcTc) #

toConstr :: RuleDecl GhcTc -> Constr #

dataTypeOf :: RuleDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcTc -> RuleDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcTc -> m (RuleDecl GhcTc) #

Data (RuleDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcRn) #

toConstr :: RuleDecl GhcRn -> Constr #

dataTypeOf :: RuleDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcRn -> RuleDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcRn -> m (RuleDecl GhcRn) #

Data (RuleDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecl GhcPs) #

toConstr :: RuleDecl GhcPs -> Constr #

dataTypeOf :: RuleDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> RuleDecl GhcPs -> RuleDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecl GhcPs -> m (RuleDecl GhcPs) #

Data (RuleDecls GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcTc) #

toConstr :: RuleDecls GhcTc -> Constr #

dataTypeOf :: RuleDecls GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcTc -> RuleDecls GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcTc -> m (RuleDecls GhcTc) #

Data (RuleDecls GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcRn) #

toConstr :: RuleDecls GhcRn -> Constr #

dataTypeOf :: RuleDecls GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcRn -> RuleDecls GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcRn -> m (RuleDecls GhcRn) #

Data (RuleDecls GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RuleDecls GhcPs) #

toConstr :: RuleDecls GhcPs -> Constr #

dataTypeOf :: RuleDecls GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (RuleDecls GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RuleDecls GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> RuleDecls GhcPs -> RuleDecls GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleDecls GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> RuleDecls GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleDecls GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleDecls GhcPs -> m (RuleDecls GhcPs) #

Data (ForeignDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcTc) #

toConstr :: ForeignDecl GhcTc -> Constr #

dataTypeOf :: ForeignDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcTc -> ForeignDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcTc -> m (ForeignDecl GhcTc) #

Data (ForeignDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcRn) #

toConstr :: ForeignDecl GhcRn -> Constr #

dataTypeOf :: ForeignDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcRn -> ForeignDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcRn -> m (ForeignDecl GhcRn) #

Data (ForeignDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForeignDecl GhcPs) #

toConstr :: ForeignDecl GhcPs -> Constr #

dataTypeOf :: ForeignDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ForeignDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForeignDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ForeignDecl GhcPs -> ForeignDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForeignDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ForeignDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForeignDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForeignDecl GhcPs -> m (ForeignDecl GhcPs) #

Data (DefaultDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcTc) #

toConstr :: DefaultDecl GhcTc -> Constr #

dataTypeOf :: DefaultDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcTc -> DefaultDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcTc -> m (DefaultDecl GhcTc) #

Data (DefaultDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcRn) #

toConstr :: DefaultDecl GhcRn -> Constr #

dataTypeOf :: DefaultDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcRn -> DefaultDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcRn -> m (DefaultDecl GhcRn) #

Data (DefaultDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DefaultDecl GhcPs) #

toConstr :: DefaultDecl GhcPs -> Constr #

dataTypeOf :: DefaultDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DefaultDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DefaultDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> DefaultDecl GhcPs -> DefaultDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefaultDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefaultDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefaultDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefaultDecl GhcPs -> m (DefaultDecl GhcPs) #

Data (DerivStrategy GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcTc) #

toConstr :: DerivStrategy GhcTc -> Constr #

dataTypeOf :: DerivStrategy GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcTc -> DerivStrategy GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcTc -> m (DerivStrategy GhcTc) #

Data (DerivStrategy GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcRn) #

toConstr :: DerivStrategy GhcRn -> Constr #

dataTypeOf :: DerivStrategy GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcRn -> DerivStrategy GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcRn -> m (DerivStrategy GhcRn) #

Data (DerivStrategy GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivStrategy GhcPs) #

toConstr :: DerivStrategy GhcPs -> Constr #

dataTypeOf :: DerivStrategy GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivStrategy GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivStrategy GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> DerivStrategy GhcPs -> DerivStrategy GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivStrategy GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> DerivStrategy GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivStrategy GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivStrategy GhcPs -> m (DerivStrategy GhcPs) #

Data (DerivDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcTc) #

toConstr :: DerivDecl GhcTc -> Constr #

dataTypeOf :: DerivDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcTc -> DerivDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcTc -> m (DerivDecl GhcTc) #

Data (DerivDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcRn) #

toConstr :: DerivDecl GhcRn -> Constr #

dataTypeOf :: DerivDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcRn -> DerivDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcRn -> m (DerivDecl GhcRn) #

Data (DerivDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DerivDecl GhcPs) #

toConstr :: DerivDecl GhcPs -> Constr #

dataTypeOf :: DerivDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DerivDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DerivDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> DerivDecl GhcPs -> DerivDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DerivDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> DerivDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DerivDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DerivDecl GhcPs -> m (DerivDecl GhcPs) #

Data (InstDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcTc) #

toConstr :: InstDecl GhcTc -> Constr #

dataTypeOf :: InstDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcTc -> InstDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcTc -> m (InstDecl GhcTc) #

Data (InstDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcRn) #

toConstr :: InstDecl GhcRn -> Constr #

dataTypeOf :: InstDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcRn -> InstDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcRn -> m (InstDecl GhcRn) #

Data (InstDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstDecl GhcPs) #

toConstr :: InstDecl GhcPs -> Constr #

dataTypeOf :: InstDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> InstDecl GhcPs -> InstDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstDecl GhcPs -> m (InstDecl GhcPs) #

Data (ClsInstDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcTc) #

toConstr :: ClsInstDecl GhcTc -> Constr #

dataTypeOf :: ClsInstDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcTc -> ClsInstDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcTc -> m (ClsInstDecl GhcTc) #

Data (ClsInstDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcRn) #

toConstr :: ClsInstDecl GhcRn -> Constr #

dataTypeOf :: ClsInstDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcRn -> ClsInstDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcRn -> m (ClsInstDecl GhcRn) #

Data (ClsInstDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ClsInstDecl GhcPs) #

toConstr :: ClsInstDecl GhcPs -> Constr #

dataTypeOf :: ClsInstDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ClsInstDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ClsInstDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ClsInstDecl GhcPs -> ClsInstDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClsInstDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ClsInstDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ClsInstDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClsInstDecl GhcPs -> m (ClsInstDecl GhcPs) #

Data (DataFamInstDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcTc) #

toConstr :: DataFamInstDecl GhcTc -> Constr #

dataTypeOf :: DataFamInstDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcTc -> DataFamInstDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcTc -> m (DataFamInstDecl GhcTc) #

Data (DataFamInstDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcRn) #

toConstr :: DataFamInstDecl GhcRn -> Constr #

dataTypeOf :: DataFamInstDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcRn -> DataFamInstDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcRn -> m (DataFamInstDecl GhcRn) #

Data (DataFamInstDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DataFamInstDecl GhcPs) #

toConstr :: DataFamInstDecl GhcPs -> Constr #

dataTypeOf :: DataFamInstDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (DataFamInstDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (DataFamInstDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> DataFamInstDecl GhcPs -> DataFamInstDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataFamInstDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataFamInstDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataFamInstDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataFamInstDecl GhcPs -> m (DataFamInstDecl GhcPs) #

Data (TyFamInstDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcTc) #

toConstr :: TyFamInstDecl GhcTc -> Constr #

dataTypeOf :: TyFamInstDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcTc -> TyFamInstDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcTc -> m (TyFamInstDecl GhcTc) #

Data (TyFamInstDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcRn) #

toConstr :: TyFamInstDecl GhcRn -> Constr #

dataTypeOf :: TyFamInstDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcRn -> TyFamInstDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcRn -> m (TyFamInstDecl GhcRn) #

Data (TyFamInstDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyFamInstDecl GhcPs) #

toConstr :: TyFamInstDecl GhcPs -> Constr #

dataTypeOf :: TyFamInstDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyFamInstDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyFamInstDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> TyFamInstDecl GhcPs -> TyFamInstDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyFamInstDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyFamInstDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyFamInstDecl GhcPs -> m (TyFamInstDecl GhcPs) #

Data (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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcTc) #

toConstr :: ConDecl GhcTc -> Constr #

dataTypeOf :: ConDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcTc -> ConDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcTc -> m (ConDecl GhcTc) #

Data (ConDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcRn) #

toConstr :: ConDecl GhcRn -> Constr #

dataTypeOf :: ConDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcRn -> ConDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcRn -> m (ConDecl GhcRn) #

Data (ConDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDecl GhcPs) #

toConstr :: ConDecl GhcPs -> Constr #

dataTypeOf :: ConDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ConDecl GhcPs -> ConDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDecl GhcPs -> m (ConDecl GhcPs) #

Data (StandaloneKindSig GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcTc) #

toConstr :: StandaloneKindSig GhcTc -> Constr #

dataTypeOf :: StandaloneKindSig GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcTc -> StandaloneKindSig GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcTc -> m (StandaloneKindSig GhcTc) #

Data (StandaloneKindSig GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcRn) #

toConstr :: StandaloneKindSig GhcRn -> Constr #

dataTypeOf :: StandaloneKindSig GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcRn -> StandaloneKindSig GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcRn -> m (StandaloneKindSig GhcRn) #

Data (StandaloneKindSig GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StandaloneKindSig GhcPs) #

toConstr :: StandaloneKindSig GhcPs -> Constr #

dataTypeOf :: StandaloneKindSig GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StandaloneKindSig GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StandaloneKindSig GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> StandaloneKindSig GhcPs -> StandaloneKindSig GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StandaloneKindSig GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> StandaloneKindSig GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StandaloneKindSig GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StandaloneKindSig GhcPs -> m (StandaloneKindSig GhcPs) #

Data (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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcTc) #

toConstr :: HsDerivingClause GhcTc -> Constr #

dataTypeOf :: HsDerivingClause GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcTc -> HsDerivingClause GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcTc -> m (HsDerivingClause GhcTc) #

Data (HsDerivingClause GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcRn) #

toConstr :: HsDerivingClause GhcRn -> Constr #

dataTypeOf :: HsDerivingClause GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcRn -> HsDerivingClause GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcRn -> m (HsDerivingClause GhcRn) #

Data (HsDerivingClause GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDerivingClause GhcPs) #

toConstr :: HsDerivingClause GhcPs -> Constr #

dataTypeOf :: HsDerivingClause GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDerivingClause GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDerivingClause GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsDerivingClause GhcPs -> HsDerivingClause GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDerivingClause GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDerivingClause GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDerivingClause GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDerivingClause GhcPs -> m (HsDerivingClause GhcPs) #

Data (HsDataDefn GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcTc) #

toConstr :: HsDataDefn GhcTc -> Constr #

dataTypeOf :: HsDataDefn GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcTc -> HsDataDefn GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcTc -> m (HsDataDefn GhcTc) #

Data (HsDataDefn GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcRn) #

toConstr :: HsDataDefn GhcRn -> Constr #

dataTypeOf :: HsDataDefn GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcRn -> HsDataDefn GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcRn -> m (HsDataDefn GhcRn) #

Data (HsDataDefn GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDataDefn GhcPs) #

toConstr :: HsDataDefn GhcPs -> Constr #

dataTypeOf :: HsDataDefn GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDataDefn GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDataDefn GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsDataDefn GhcPs -> HsDataDefn GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDataDefn GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDataDefn GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDataDefn GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDataDefn GhcPs -> m (HsDataDefn GhcPs) #

Data (FamilyInfo GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcTc) #

toConstr :: FamilyInfo GhcTc -> Constr #

dataTypeOf :: FamilyInfo GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcTc -> FamilyInfo GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcTc -> m (FamilyInfo GhcTc) #

Data (FamilyInfo GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcRn) #

toConstr :: FamilyInfo GhcRn -> Constr #

dataTypeOf :: FamilyInfo GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcRn -> FamilyInfo GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcRn -> m (FamilyInfo GhcRn) #

Data (FamilyInfo GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyInfo GhcPs) #

toConstr :: FamilyInfo GhcPs -> Constr #

dataTypeOf :: FamilyInfo GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyInfo GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyInfo GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyInfo GhcPs -> FamilyInfo GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyInfo GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyInfo GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyInfo GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyInfo GhcPs -> m (FamilyInfo GhcPs) #

Data (InjectivityAnn GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcTc) #

toConstr :: InjectivityAnn GhcTc -> Constr #

dataTypeOf :: InjectivityAnn GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcTc -> InjectivityAnn GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcTc -> m (InjectivityAnn GhcTc) #

Data (InjectivityAnn GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcRn) #

toConstr :: InjectivityAnn GhcRn -> Constr #

dataTypeOf :: InjectivityAnn GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcRn -> InjectivityAnn GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcRn -> m (InjectivityAnn GhcRn) #

Data (InjectivityAnn GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InjectivityAnn GhcPs) #

toConstr :: InjectivityAnn GhcPs -> Constr #

dataTypeOf :: InjectivityAnn GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InjectivityAnn GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InjectivityAnn GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> InjectivityAnn GhcPs -> InjectivityAnn GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InjectivityAnn GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InjectivityAnn GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InjectivityAnn GhcPs -> m (InjectivityAnn GhcPs) #

Data (FamilyDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcTc) #

toConstr :: FamilyDecl GhcTc -> Constr #

dataTypeOf :: FamilyDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcTc -> FamilyDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcTc -> m (FamilyDecl GhcTc) #

Data (FamilyDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcRn) #

toConstr :: FamilyDecl GhcRn -> Constr #

dataTypeOf :: FamilyDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcRn -> FamilyDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcRn -> m (FamilyDecl GhcRn) #

Data (FamilyDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyDecl GhcPs) #

toConstr :: FamilyDecl GhcPs -> Constr #

dataTypeOf :: FamilyDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyDecl GhcPs -> FamilyDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyDecl GhcPs -> m (FamilyDecl GhcPs) #

Data (FamilyResultSig GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcTc) #

toConstr :: FamilyResultSig GhcTc -> Constr #

dataTypeOf :: FamilyResultSig GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcTc -> FamilyResultSig GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcTc -> m (FamilyResultSig GhcTc) #

Data (FamilyResultSig GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcRn) #

toConstr :: FamilyResultSig GhcRn -> Constr #

dataTypeOf :: FamilyResultSig GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcRn -> FamilyResultSig GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcRn -> m (FamilyResultSig GhcRn) #

Data (FamilyResultSig GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamilyResultSig GhcPs) #

toConstr :: FamilyResultSig GhcPs -> Constr #

dataTypeOf :: FamilyResultSig GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamilyResultSig GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamilyResultSig GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> FamilyResultSig GhcPs -> FamilyResultSig GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamilyResultSig GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamilyResultSig GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamilyResultSig GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamilyResultSig GhcPs -> m (FamilyResultSig GhcPs) #

Data (TyClGroup GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcTc) #

toConstr :: TyClGroup GhcTc -> Constr #

dataTypeOf :: TyClGroup GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcTc -> TyClGroup GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcTc -> m (TyClGroup GhcTc) #

Data (TyClGroup GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcRn) #

toConstr :: TyClGroup GhcRn -> Constr #

dataTypeOf :: TyClGroup GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcRn -> TyClGroup GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcRn -> m (TyClGroup GhcRn) #

Data (TyClGroup GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClGroup GhcPs) #

toConstr :: TyClGroup GhcPs -> Constr #

dataTypeOf :: TyClGroup GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClGroup GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClGroup GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> TyClGroup GhcPs -> TyClGroup GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClGroup GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyClGroup GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClGroup GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClGroup GhcPs -> m (TyClGroup GhcPs) #

Data (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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcTc) #

toConstr :: TyClDecl GhcTc -> Constr #

dataTypeOf :: TyClDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcTc -> TyClDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcTc -> m (TyClDecl GhcTc) #

Data (TyClDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcRn) #

toConstr :: TyClDecl GhcRn -> Constr #

dataTypeOf :: TyClDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcRn -> TyClDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcRn -> m (TyClDecl GhcRn) #

Data (TyClDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyClDecl GhcPs) #

toConstr :: TyClDecl GhcPs -> Constr #

dataTypeOf :: TyClDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyClDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyClDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> TyClDecl GhcPs -> TyClDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyClDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> TyClDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TyClDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyClDecl GhcPs -> m (TyClDecl GhcPs) #

Data (SpliceDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcTc) #

toConstr :: SpliceDecl GhcTc -> Constr #

dataTypeOf :: SpliceDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcTc -> SpliceDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcTc -> m (SpliceDecl GhcTc) #

Data (SpliceDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcRn) #

toConstr :: SpliceDecl GhcRn -> Constr #

dataTypeOf :: SpliceDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcRn -> SpliceDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcRn -> m (SpliceDecl GhcRn) #

Data (SpliceDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SpliceDecl GhcPs) #

toConstr :: SpliceDecl GhcPs -> Constr #

dataTypeOf :: SpliceDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SpliceDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SpliceDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> SpliceDecl GhcPs -> SpliceDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceDecl GhcPs -> m (SpliceDecl GhcPs) #

Data (HsGroup GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcTc) #

toConstr :: HsGroup GhcTc -> Constr #

dataTypeOf :: HsGroup GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcTc -> HsGroup GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcTc -> m (HsGroup GhcTc) #

Data (HsGroup GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcRn) #

toConstr :: HsGroup GhcRn -> Constr #

dataTypeOf :: HsGroup GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcRn -> HsGroup GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcRn -> m (HsGroup GhcRn) #

Data (HsGroup GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsGroup GhcPs) #

toConstr :: HsGroup GhcPs -> Constr #

dataTypeOf :: HsGroup GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsGroup GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsGroup GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsGroup GhcPs -> HsGroup GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsGroup GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsGroup GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsGroup GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsGroup GhcPs -> m (HsGroup GhcPs) #

Data (HsDecl GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcTc) #

toConstr :: HsDecl GhcTc -> Constr #

dataTypeOf :: HsDecl GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcTc -> HsDecl GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcTc -> m (HsDecl GhcTc) #

Data (HsDecl GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcRn) #

toConstr :: HsDecl GhcRn -> Constr #

dataTypeOf :: HsDecl GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcRn -> HsDecl GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcRn -> m (HsDecl GhcRn) #

Data (HsDecl GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsDecl GhcPs) #

toConstr :: HsDecl GhcPs -> Constr #

dataTypeOf :: HsDecl GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsDecl GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsDecl GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsDecl GhcPs -> HsDecl GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsDecl GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsDecl GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsDecl GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsDecl GhcPs -> m (HsDecl GhcPs) #

Data (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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcTc) #

toConstr :: ArithSeqInfo GhcTc -> Constr #

dataTypeOf :: ArithSeqInfo GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcTc -> ArithSeqInfo GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcTc -> m (ArithSeqInfo GhcTc) #

Data (ArithSeqInfo GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcRn) #

toConstr :: ArithSeqInfo GhcRn -> Constr #

dataTypeOf :: ArithSeqInfo GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcRn -> ArithSeqInfo GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcRn -> m (ArithSeqInfo GhcRn) #

Data (ArithSeqInfo GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ArithSeqInfo GhcPs) #

toConstr :: ArithSeqInfo GhcPs -> Constr #

dataTypeOf :: ArithSeqInfo GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ArithSeqInfo GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ArithSeqInfo GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ArithSeqInfo GhcPs -> ArithSeqInfo GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArithSeqInfo GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ArithSeqInfo GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArithSeqInfo GhcPs -> m (ArithSeqInfo GhcPs) #

Data (HsBracket GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcTc) #

toConstr :: HsBracket GhcTc -> Constr #

dataTypeOf :: HsBracket GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcTc -> HsBracket GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcTc -> m (HsBracket GhcTc) #

Data (HsBracket GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcRn) #

toConstr :: HsBracket GhcRn -> Constr #

dataTypeOf :: HsBracket GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcRn -> HsBracket GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcRn -> m (HsBracket GhcRn) #

Data (HsBracket GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBracket GhcPs) #

toConstr :: HsBracket GhcPs -> Constr #

dataTypeOf :: HsBracket GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBracket GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBracket GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsBracket GhcPs -> HsBracket GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBracket GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsBracket GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBracket GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBracket GhcPs -> m (HsBracket GhcPs) #

Data (HsSplicedThing GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcTc) #

toConstr :: HsSplicedThing GhcTc -> Constr #

dataTypeOf :: HsSplicedThing GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcTc -> HsSplicedThing GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcTc -> m (HsSplicedThing GhcTc) #

Data (HsSplicedThing GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcRn) #

toConstr :: HsSplicedThing GhcRn -> Constr #

dataTypeOf :: HsSplicedThing GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcRn -> HsSplicedThing GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcRn -> m (HsSplicedThing GhcRn) #

Data (HsSplicedThing GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSplicedThing GhcPs) #

toConstr :: HsSplicedThing GhcPs -> Constr #

dataTypeOf :: HsSplicedThing GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSplicedThing GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSplicedThing GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsSplicedThing GhcPs -> HsSplicedThing GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSplicedThing GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsSplicedThing GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSplicedThing GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSplicedThing GhcPs -> m (HsSplicedThing GhcPs) #

Data (ApplicativeArg GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcTc) #

toConstr :: ApplicativeArg GhcTc -> Constr #

dataTypeOf :: ApplicativeArg GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcTc -> ApplicativeArg GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcTc -> m (ApplicativeArg GhcTc) #

Data (ApplicativeArg GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcRn) #

toConstr :: ApplicativeArg GhcRn -> Constr #

dataTypeOf :: ApplicativeArg GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcRn -> ApplicativeArg GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcRn -> m (ApplicativeArg GhcRn) #

Data (ApplicativeArg GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ApplicativeArg GhcPs) #

toConstr :: ApplicativeArg GhcPs -> Constr #

dataTypeOf :: ApplicativeArg GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ApplicativeArg GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ApplicativeArg GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ApplicativeArg GhcPs -> ApplicativeArg GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ApplicativeArg GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ApplicativeArg GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ApplicativeArg GhcPs -> m (ApplicativeArg GhcPs) #

Data (HsCmdTop GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcTc) #

toConstr :: HsCmdTop GhcTc -> Constr #

dataTypeOf :: HsCmdTop GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcTc -> HsCmdTop GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcTc -> m (HsCmdTop GhcTc) #

Data (HsCmdTop GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcRn) #

toConstr :: HsCmdTop GhcRn -> Constr #

dataTypeOf :: HsCmdTop GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcRn -> HsCmdTop GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcRn -> m (HsCmdTop GhcRn) #

Data (HsCmdTop GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsCmdTop GhcPs) #

toConstr :: HsCmdTop GhcPs -> Constr #

dataTypeOf :: HsCmdTop GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsCmdTop GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsCmdTop GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsCmdTop GhcPs -> HsCmdTop GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsCmdTop GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsCmdTop GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsCmdTop GhcPs -> m (HsCmdTop GhcPs) #

Data (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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcTc) #

toConstr :: HsTupArg GhcTc -> Constr #

dataTypeOf :: HsTupArg GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcTc -> HsTupArg GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcTc -> m (HsTupArg GhcTc) #

Data (HsTupArg GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcRn) #

toConstr :: HsTupArg GhcRn -> Constr #

dataTypeOf :: HsTupArg GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcRn -> HsTupArg GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcRn -> m (HsTupArg GhcRn) #

Data (HsTupArg GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTupArg GhcPs) #

toConstr :: HsTupArg GhcPs -> Constr #

dataTypeOf :: HsTupArg GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTupArg GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTupArg GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsTupArg GhcPs -> HsTupArg GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupArg GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsTupArg GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupArg GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupArg GhcPs -> m (HsTupArg GhcPs) #

Data (HsModule GhcTc) Source # 
Instance details

Defined in GHC.Hs

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcTc -> c (HsModule GhcTc) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcTc) #

toConstr :: HsModule GhcTc -> Constr #

dataTypeOf :: HsModule GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsModule GhcTc -> HsModule GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcTc -> m (HsModule GhcTc) #

Data (HsModule GhcRn) Source # 
Instance details

Defined in GHC.Hs

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcRn -> c (HsModule GhcRn) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcRn) #

toConstr :: HsModule GhcRn -> Constr #

dataTypeOf :: HsModule GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsModule GhcRn -> HsModule GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcRn -> m (HsModule GhcRn) #

Data (HsModule GhcPs) Source # 
Instance details

Defined in GHC.Hs

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsModule GhcPs -> c (HsModule GhcPs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsModule GhcPs) #

toConstr :: HsModule GhcPs -> Constr #

dataTypeOf :: HsModule GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsModule GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsModule GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsModule GhcPs -> HsModule GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsModule GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsModule GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsModule GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsModule GhcPs -> m (HsModule GhcPs) #

Ord (XCFieldOcc (GhcPass p)) => Ord (FieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

OutputableBndr (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

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 #

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

OutputableBndrId p => Outputable (SyntaxExpr (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 (HsCmd (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 (HsOverLit (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Lit

Outputable (HsLit (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Lit

Outputable (AmbiguousFieldOcc (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

OutputableBndrId p => Outputable (HsType (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

OutputableBndrId p => Outputable (HsTyVarBndr (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Types

OutputableBndrId p => Outputable (FixitySig (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 (IPBind (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 (ABExport (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Binds

OutputableBndr (IdP (GhcPass p)) => Outputable (RoleAnnotDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (AnnDecl (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 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 (ForeignDecl (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 (DerivStrategy (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 (InstDecl (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 (DataFamInstDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

OutputableBndrId p => Outputable (TyFamInstDecl (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 (StandaloneKindSig (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 (HsDataDefn (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 (TyClGroup (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 (SpliceDecl (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 (HsDecl (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Decls

(Outputable (GhcPass p), Outputable (NameOrRdrName (GhcPass p))) => Outputable (HsStmtContext (GhcPass p)) 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 (HsSplicedThing (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Expr

OutputableBndrId idL => Outputable (ApplicativeArg (GhcPass idL)) 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 (HsModule (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs

Outputable (PatBuilder GhcPs) Source # 
Instance details

Defined in RdrHsSyn

NamedThing (HsTyVarBndr GhcRn) Source # 
Instance details

Defined in GHC.Hs.Types

DisambECP (PatBuilder GhcPs) Source # 
Instance details

Defined in RdrHsSyn

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 #

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 #

mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> Located (PatBuilder GhcPs) -> Bool -> Located (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) Source #

mkHsDoPV :: SrcSpan -> 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 #

mkSumOrTuplePV :: SrcSpan -> Boxity -> SumOrTuple (PatBuilder GhcPs) -> PV (Located (PatBuilder GhcPs)) 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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcTc body) #

toConstr :: GRHSs GhcTc body -> Constr #

dataTypeOf :: GRHSs GhcTc body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcTc body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcTc body)) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcTc body -> GRHSs GhcTc body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcTc body -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcTc body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcTc body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcTc body -> m (GRHSs GhcTc body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcRn body) #

toConstr :: GRHSs GhcRn body -> Constr #

dataTypeOf :: GRHSs GhcRn body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcRn body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcRn body)) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcRn body -> GRHSs GhcRn body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcRn body -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcRn body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcRn body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcRn body -> m (GRHSs GhcRn body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHSs GhcPs body) #

toConstr :: GRHSs GhcPs body -> Constr #

dataTypeOf :: GRHSs GhcPs body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHSs GhcPs body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHSs GhcPs body)) #

gmapT :: (forall b. Data b => b -> b) -> GRHSs GhcPs body -> GRHSs GhcPs body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHSs GhcPs body -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHSs GhcPs body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHSs GhcPs body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHSs GhcPs body -> m (GRHSs GhcPs body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcTc body) #

toConstr :: MatchGroup GhcTc body -> Constr #

dataTypeOf :: MatchGroup GhcTc body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcTc body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcTc body)) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcTc body -> MatchGroup GhcTc body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcTc body -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcTc body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcTc body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcTc body -> m (MatchGroup GhcTc body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcRn body) #

toConstr :: MatchGroup GhcRn body -> Constr #

dataTypeOf :: MatchGroup GhcRn body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcRn body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcRn body)) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcRn body -> MatchGroup GhcRn body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcRn body -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcRn body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcRn body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcRn body -> m (MatchGroup GhcRn body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MatchGroup GhcPs body) #

toConstr :: MatchGroup GhcPs body -> Constr #

dataTypeOf :: MatchGroup GhcPs body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MatchGroup GhcPs body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MatchGroup GhcPs body)) #

gmapT :: (forall b. Data b => b -> b) -> MatchGroup GhcPs body -> MatchGroup GhcPs body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MatchGroup GhcPs body -> r #

gmapQ :: (forall d. Data d => d -> u) -> MatchGroup GhcPs body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MatchGroup GhcPs body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MatchGroup GhcPs body -> m (MatchGroup GhcPs body) #

Data (HsArg (LHsType GhcTc) (LHsKind 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) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

toConstr :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> Constr #

dataTypeOf :: HsArg (LHsType GhcTc) (LHsKind GhcTc) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcTc) (LHsKind GhcTc))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcTc) (LHsKind GhcTc))) #

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcTc) (LHsKind GhcTc) -> m (HsArg (LHsType GhcTc) (LHsKind GhcTc)) #

Data (HsArg (LHsType GhcRn) (LHsKind 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) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

toConstr :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> Constr #

dataTypeOf :: HsArg (LHsType GhcRn) (LHsKind GhcRn) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcRn) (LHsKind GhcRn))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcRn) (LHsKind GhcRn))) #

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcRn) (LHsKind GhcRn) -> m (HsArg (LHsType GhcRn) (LHsKind GhcRn)) #

Data (HsArg (LHsType GhcPs) (LHsKind 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) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

toConstr :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> Constr #

dataTypeOf :: HsArg (LHsType GhcPs) (LHsKind GhcPs) -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg (LHsType GhcPs) (LHsKind GhcPs))) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg (LHsType GhcPs) (LHsKind GhcPs))) #

gmapT :: (forall b. Data b => b -> b) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg (LHsType GhcPs) (LHsKind GhcPs) -> m (HsArg (LHsType GhcPs) (LHsKind GhcPs)) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcTc thing) #

toConstr :: HsWildCardBndrs GhcTc thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcTc thing -> HsWildCardBndrs GhcTc thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) #

Data thing => Data (HsWildCardBndrs GhcRn thing) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcRn thing) #

toConstr :: HsWildCardBndrs GhcRn thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcRn thing -> HsWildCardBndrs GhcRn thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) #

Data thing => Data (HsWildCardBndrs GhcPs thing) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcPs thing) #

toConstr :: HsWildCardBndrs GhcPs thing -> Constr #

dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcPs thing -> HsWildCardBndrs GhcPs thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) #

Data 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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcTc thing) #

toConstr :: HsImplicitBndrs GhcTc thing -> Constr #

dataTypeOf :: HsImplicitBndrs GhcTc thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcTc thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcTc thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcTc thing -> HsImplicitBndrs GhcTc thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcTc thing -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcTc thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcTc thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcTc thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcTc thing -> m (HsImplicitBndrs GhcTc thing) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcRn thing) #

toConstr :: HsImplicitBndrs GhcRn thing -> Constr #

dataTypeOf :: HsImplicitBndrs GhcRn thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcRn thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcRn thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcRn thing -> HsImplicitBndrs GhcRn thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcRn thing -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcRn thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcRn thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcRn thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcRn thing -> m (HsImplicitBndrs GhcRn thing) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs GhcPs thing) #

toConstr :: HsImplicitBndrs GhcPs thing -> Constr #

dataTypeOf :: HsImplicitBndrs GhcPs thing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs GhcPs thing)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs GhcPs thing)) #

gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs GhcPs thing -> HsImplicitBndrs GhcPs thing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcPs thing -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs GhcPs thing -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs GhcPs thing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs GhcPs thing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs GhcPs thing -> m (HsImplicitBndrs GhcPs thing) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcTc GhcTc) #

toConstr :: PatSynBind GhcTc GhcTc -> Constr #

dataTypeOf :: PatSynBind GhcTc GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcTc GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcTc GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcTc GhcTc -> PatSynBind GhcTc GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcTc GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcTc GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcTc GhcTc -> m (PatSynBind GhcTc GhcTc) #

Data (PatSynBind GhcRn GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcRn GhcRn) #

toConstr :: PatSynBind GhcRn GhcRn -> Constr #

dataTypeOf :: PatSynBind GhcRn GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcRn GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcRn GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcRn GhcRn -> PatSynBind GhcRn GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcRn GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcRn GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcRn GhcRn -> m (PatSynBind GhcRn GhcRn) #

Data (PatSynBind GhcPs GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcRn) #

toConstr :: PatSynBind GhcPs GhcRn -> Constr #

dataTypeOf :: PatSynBind GhcPs GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcRn -> PatSynBind GhcPs GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcRn -> m (PatSynBind GhcPs GhcRn) #

Data (PatSynBind GhcPs GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PatSynBind GhcPs GhcPs) #

toConstr :: PatSynBind GhcPs GhcPs -> Constr #

dataTypeOf :: PatSynBind GhcPs GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (PatSynBind GhcPs GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PatSynBind GhcPs GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> PatSynBind GhcPs GhcPs -> PatSynBind GhcPs GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynBind GhcPs GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynBind GhcPs GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynBind GhcPs GhcPs -> m (PatSynBind GhcPs GhcPs) #

Data (HsBindLR GhcTc GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcTc GhcTc) #

toConstr :: HsBindLR GhcTc GhcTc -> Constr #

dataTypeOf :: HsBindLR GhcTc GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcTc GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcTc GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcTc GhcTc -> HsBindLR GhcTc GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcTc GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcTc GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcTc GhcTc -> m (HsBindLR GhcTc GhcTc) #

Data (HsBindLR GhcRn GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcRn GhcRn) #

toConstr :: HsBindLR GhcRn GhcRn -> Constr #

dataTypeOf :: HsBindLR GhcRn GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcRn GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcRn GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcRn GhcRn -> HsBindLR GhcRn GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcRn GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcRn GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcRn GhcRn -> m (HsBindLR GhcRn GhcRn) #

Data (HsBindLR GhcPs GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcRn) #

toConstr :: HsBindLR GhcPs GhcRn -> Constr #

dataTypeOf :: HsBindLR GhcPs GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcRn -> HsBindLR GhcPs GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcRn -> m (HsBindLR GhcPs GhcRn) #

Data (HsBindLR GhcPs GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBindLR GhcPs GhcPs) #

toConstr :: HsBindLR GhcPs GhcPs -> Constr #

dataTypeOf :: HsBindLR GhcPs GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBindLR GhcPs GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBindLR GhcPs GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsBindLR GhcPs GhcPs -> HsBindLR GhcPs GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBindLR GhcPs GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBindLR GhcPs GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBindLR GhcPs GhcPs -> m (HsBindLR GhcPs GhcPs) #

Data (HsValBindsLR GhcTc GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcTc GhcTc) #

toConstr :: HsValBindsLR GhcTc GhcTc -> Constr #

dataTypeOf :: HsValBindsLR GhcTc GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcTc GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcTc GhcTc -> HsValBindsLR GhcTc GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcTc GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcTc GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcTc GhcTc -> m (HsValBindsLR GhcTc GhcTc) #

Data (HsValBindsLR GhcRn GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcRn GhcRn) #

toConstr :: HsValBindsLR GhcRn GhcRn -> Constr #

dataTypeOf :: HsValBindsLR GhcRn GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcRn GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcRn GhcRn -> HsValBindsLR GhcRn GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcRn GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcRn GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcRn GhcRn -> m (HsValBindsLR GhcRn GhcRn) #

Data (HsValBindsLR GhcPs GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcRn) #

toConstr :: HsValBindsLR GhcPs GhcRn -> Constr #

dataTypeOf :: HsValBindsLR GhcPs GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcRn -> HsValBindsLR GhcPs GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcRn -> m (HsValBindsLR GhcPs GhcRn) #

Data (HsValBindsLR GhcPs GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsValBindsLR GhcPs GhcPs) #

toConstr :: HsValBindsLR GhcPs GhcPs -> Constr #

dataTypeOf :: HsValBindsLR GhcPs GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsValBindsLR GhcPs GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsValBindsLR GhcPs GhcPs -> HsValBindsLR GhcPs GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsValBindsLR GhcPs GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsValBindsLR GhcPs GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsValBindsLR GhcPs GhcPs -> m (HsValBindsLR GhcPs GhcPs) #

Data (HsLocalBindsLR GhcTc GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcTc GhcTc) #

toConstr :: HsLocalBindsLR GhcTc GhcTc -> Constr #

dataTypeOf :: HsLocalBindsLR GhcTc GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcTc GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcTc GhcTc -> HsLocalBindsLR GhcTc GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcTc GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcTc GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcTc GhcTc -> m (HsLocalBindsLR GhcTc GhcTc) #

Data (HsLocalBindsLR GhcRn GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcRn GhcRn) #

toConstr :: HsLocalBindsLR GhcRn GhcRn -> Constr #

dataTypeOf :: HsLocalBindsLR GhcRn GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcRn GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcRn GhcRn -> HsLocalBindsLR GhcRn GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcRn GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcRn GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcRn GhcRn -> m (HsLocalBindsLR GhcRn GhcRn) #

Data (HsLocalBindsLR GhcPs GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcRn) #

toConstr :: HsLocalBindsLR GhcPs GhcRn -> Constr #

dataTypeOf :: HsLocalBindsLR GhcPs GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcRn -> HsLocalBindsLR GhcPs GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcRn -> m (HsLocalBindsLR GhcPs GhcRn) #

Data (HsLocalBindsLR GhcPs GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsLocalBindsLR GhcPs GhcPs) #

toConstr :: HsLocalBindsLR GhcPs GhcPs -> Constr #

dataTypeOf :: HsLocalBindsLR GhcPs GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsLocalBindsLR GhcPs GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> HsLocalBindsLR GhcPs GhcPs -> HsLocalBindsLR GhcPs GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsLocalBindsLR GhcPs GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsLocalBindsLR GhcPs GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsLocalBindsLR GhcPs GhcPs -> m (HsLocalBindsLR GhcPs GhcPs) #

Data 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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcTc body) #

toConstr :: HsRecFields GhcTc body -> Constr #

dataTypeOf :: HsRecFields GhcTc body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcTc body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcTc body)) #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcTc body -> HsRecFields GhcTc body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) #

Data body => Data (HsRecFields GhcRn body) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcRn body) #

toConstr :: HsRecFields GhcRn body -> Constr #

dataTypeOf :: HsRecFields GhcRn body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcRn body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcRn body)) #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcRn body -> HsRecFields GhcRn body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) #

Data body => Data (HsRecFields GhcPs body) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcPs body) #

toConstr :: HsRecFields GhcPs body -> Constr #

dataTypeOf :: HsRecFields GhcPs body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcPs body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcPs body)) #

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcPs body -> HsRecFields GhcPs body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) #

Data 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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcTc rhs) #

toConstr :: FamEqn GhcTc rhs -> Constr #

dataTypeOf :: FamEqn GhcTc rhs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcTc rhs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcTc rhs)) #

gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcTc rhs -> FamEqn GhcTc rhs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcTc rhs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcTc rhs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcTc rhs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcTc rhs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcTc rhs -> m (FamEqn GhcTc rhs) #

Data rhs => Data (FamEqn GhcRn rhs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcRn rhs) #

toConstr :: FamEqn GhcRn rhs -> Constr #

dataTypeOf :: FamEqn GhcRn rhs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcRn rhs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcRn rhs)) #

gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcRn rhs -> FamEqn GhcRn rhs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcRn rhs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcRn rhs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcRn rhs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcRn rhs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcRn rhs -> m (FamEqn GhcRn rhs) #

Data rhs => Data (FamEqn GhcPs rhs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn GhcPs rhs) #

toConstr :: FamEqn GhcPs rhs -> Constr #

dataTypeOf :: FamEqn GhcPs rhs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn GhcPs rhs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn GhcPs rhs)) #

gmapT :: (forall b. Data b => b -> b) -> FamEqn GhcPs rhs -> FamEqn GhcPs rhs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcPs rhs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn GhcPs rhs -> r #

gmapQ :: (forall d. Data d => d -> u) -> FamEqn GhcPs rhs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn GhcPs rhs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn GhcPs rhs -> m (FamEqn GhcPs rhs) #

Data (ParStmtBlock GhcTc GhcTc) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcTc GhcTc) #

toConstr :: ParStmtBlock GhcTc GhcTc -> Constr #

dataTypeOf :: ParStmtBlock GhcTc GhcTc -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcTc GhcTc)) #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcTc GhcTc -> ParStmtBlock GhcTc GhcTc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcTc GhcTc -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcTc GhcTc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcTc GhcTc -> m (ParStmtBlock GhcTc GhcTc) #

Data (ParStmtBlock GhcRn GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcRn GhcRn) #

toConstr :: ParStmtBlock GhcRn GhcRn -> Constr #

dataTypeOf :: ParStmtBlock GhcRn GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcRn GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcRn GhcRn -> ParStmtBlock GhcRn GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcRn GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcRn GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcRn GhcRn -> m (ParStmtBlock GhcRn GhcRn) #

Data (ParStmtBlock GhcPs GhcRn) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcRn) #

toConstr :: ParStmtBlock GhcPs GhcRn -> Constr #

dataTypeOf :: ParStmtBlock GhcPs GhcRn -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcRn)) #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcRn -> ParStmtBlock GhcPs GhcRn #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcRn -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcRn -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcRn -> m (ParStmtBlock GhcPs GhcRn) #

Data (ParStmtBlock GhcPs GhcPs) Source # 
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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParStmtBlock GhcPs GhcPs) #

toConstr :: ParStmtBlock GhcPs GhcPs -> Constr #

dataTypeOf :: ParStmtBlock GhcPs GhcPs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParStmtBlock GhcPs GhcPs)) #

gmapT :: (forall b. Data b => b -> b) -> ParStmtBlock GhcPs GhcPs -> ParStmtBlock GhcPs GhcPs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParStmtBlock GhcPs GhcPs -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParStmtBlock GhcPs GhcPs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParStmtBlock GhcPs GhcPs -> m (ParStmtBlock GhcPs GhcPs) #

Data 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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcTc body) #

toConstr :: GRHS GhcTc body -> Constr #

dataTypeOf :: GRHS GhcTc body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcTc body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcTc body)) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcTc body -> GRHS GhcTc body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcTc body -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcTc body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcTc body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcTc body -> m (GRHS GhcTc body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcRn body) #

toConstr :: GRHS GhcRn body -> Constr #

dataTypeOf :: GRHS GhcRn body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcRn body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcRn body)) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcRn body -> GRHS GhcRn body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcRn body -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcRn body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcRn body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcRn body -> m (GRHS GhcRn body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GRHS GhcPs body) #

toConstr :: GRHS GhcPs body -> Constr #

dataTypeOf :: GRHS GhcPs body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (GRHS GhcPs body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (GRHS GhcPs body)) #

gmapT :: (forall b. Data b => b -> b) -> GRHS GhcPs body -> GRHS GhcPs body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GRHS GhcPs body -> r #

gmapQ :: (forall d. Data d => d -> u) -> GRHS GhcPs body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GRHS GhcPs body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GRHS GhcPs body -> m (GRHS GhcPs body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcTc body) #

toConstr :: Match GhcTc body -> Constr #

dataTypeOf :: Match GhcTc body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcTc body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcTc body)) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcTc body -> Match GhcTc body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcTc body -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcTc body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcTc body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcTc body -> m (Match GhcTc body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcRn body) #

toConstr :: Match GhcRn body -> Constr #

dataTypeOf :: Match GhcRn body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcRn body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcRn body)) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcRn body -> Match GhcRn body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcRn body -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcRn body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcRn body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcRn body -> m (Match GhcRn body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Match GhcPs body) #

toConstr :: Match GhcPs body -> Constr #

dataTypeOf :: Match GhcPs body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Match GhcPs body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Match GhcPs body)) #

gmapT :: (forall b. Data b => b -> b) -> Match GhcPs body -> Match GhcPs body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match GhcPs body -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match GhcPs body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match GhcPs body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match GhcPs body -> m (Match GhcPs body) #

Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) Source # 
Instance details

Defined in GHC.Hs.Types

Outputable thing => Outputable (HsImplicitBndrs (GhcPass p) thing) Source # 
Instance details

Defined in GHC.Hs.Types

(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 pl, OutputableBndrId pr) => Outputable (HsBindLR (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 pl, OutputableBndrId pr) => Outputable (HsLocalBindsLR (GhcPass pl) (GhcPass pr)) 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 #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcTc GhcTc body) #

toConstr :: StmtLR GhcTc GhcTc body -> Constr #

dataTypeOf :: StmtLR GhcTc GhcTc body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcTc GhcTc body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcTc GhcTc body)) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcTc GhcTc body -> StmtLR GhcTc GhcTc body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcTc GhcTc body -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcTc GhcTc body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcTc GhcTc body -> m (StmtLR GhcTc GhcTc body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcRn GhcRn body) #

toConstr :: StmtLR GhcRn GhcRn body -> Constr #

dataTypeOf :: StmtLR GhcRn GhcRn body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcRn GhcRn body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcRn GhcRn body)) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcRn GhcRn body -> StmtLR GhcRn GhcRn body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcRn GhcRn body -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcRn GhcRn body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcRn GhcRn body -> m (StmtLR GhcRn GhcRn body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcRn body) #

toConstr :: StmtLR GhcPs GhcRn body -> Constr #

dataTypeOf :: StmtLR GhcPs GhcRn body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcRn body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcRn body)) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcRn body -> StmtLR GhcPs GhcRn body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcRn body -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcRn body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcRn body -> m (StmtLR GhcPs GhcRn body) #

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StmtLR GhcPs GhcPs body) #

toConstr :: StmtLR GhcPs GhcPs body -> Constr #

dataTypeOf :: StmtLR GhcPs GhcPs body -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StmtLR GhcPs GhcPs body)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StmtLR GhcPs GhcPs body)) #

gmapT :: (forall b. Data b => b -> b) -> StmtLR GhcPs GhcPs body -> StmtLR GhcPs GhcPs body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs body -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StmtLR GhcPs GhcPs body -> r #

gmapQ :: (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs body -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StmtLR GhcPs GhcPs body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StmtLR GhcPs GhcPs body -> m (StmtLR GhcPs GhcPs body) #

(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 XCFieldOcc GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XCFieldOcc GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XCFieldOcc GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitTupleTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitTupleTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitTupleTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitListTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitListTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitListTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type XSpliceTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XSpliceTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XSpliceTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type XHsQTvs GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XHsQTvs GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XHsQTvs GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type XSigPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc = [Type]
type XSumPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XOverLit GhcTc Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcRn Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcPs Source # 
Instance details

Defined in GHC.Hs.Lit

type XCmdDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XAmbiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XAmbiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XAmbiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type XUnambiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XUnambiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XUnambiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type XStatic GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc = Type
type XDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type XHsRule GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type XIPBinds GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type IdP GhcTc Source # 
Instance details

Defined in GHC.Hs.Extension

type IdP GhcTc = Id
type IdP GhcRn Source # 
Instance details

Defined in GHC.Hs.Extension

type IdP GhcRn = Name
type IdP GhcPs Source # 
Instance details

Defined in GHC.Hs.Extension

type XHsWC GhcTc b Source # 
Instance details

Defined in GHC.Hs.Types

type XHsWC GhcTc b = [Name]
type XHsWC GhcRn b Source # 
Instance details

Defined in GHC.Hs.Types

type XHsWC GhcRn b = [Name]
type XHsWC GhcPs b Source # 
Instance details

Defined in GHC.Hs.Types

type XHsIB GhcTc _ Source # 
Instance details

Defined in GHC.Hs.Types

type XHsIB GhcTc _ = [Name]
type XHsIB GhcRn _ Source # 
Instance details

Defined in GHC.Hs.Types

type XHsIB GhcRn _ = [Name]
type XHsIB GhcPs _ Source # 
Instance details

Defined in GHC.Hs.Types

type XMG GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XPatBind GhcTc (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 GhcPs (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXIE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XXIE (GhcPass _) = NoExtCon
type XIEDocNamed (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEDoc (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEModuleContents (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingWith (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingAll (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEThingAbs (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XIEVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XXImportDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XCImportDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XXFieldOcc (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XXConDeclField (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XConDeclField (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XXTyVarBndr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XKindedTyVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XUserTyVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XXType (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XWildCardTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XTyLit (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XRecTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XBangTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XDocTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XKindSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XStarTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XIParamTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XParTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XOpTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XSumTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XTupleTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XListTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XFunTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XAppKindTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XAppTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XTyVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XQualTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XForAllTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XXLHsQTyVars (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XXPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XCoPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XLitPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XSplicePat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XBangPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XParPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XAsPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XLazyPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XVarPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type XXOverLit (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XXLit (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsDoublePrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsFloatPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsRat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsInteger (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsWord64Prim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsInt64Prim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsWordPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsIntPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsInt (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsStringPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsString (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsCharPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XHsChar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type XXApplicativeArg (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgMany (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeArgOne (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXCmd (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdWrap (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdLet (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdIf (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdCase (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdPar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdLam (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdApp (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrForm (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXCmdTop (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXBracket (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTExpBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XVarBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTypBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XDecBrG (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XDecBrL (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPatBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XExpBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXSplice (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSpliced (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XQuasiQuote (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XUntypedSplice (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTypedSplice (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXTupArg (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPresent (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXAmbiguousFieldOcc (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type XXExpr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XWrap (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTickPragma (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XBinTick (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTick (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XProc (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSpliceE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XTcBracketOut (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XRnBracketOut (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XBracket (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCoreAnn (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSCC (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XExprWithTySig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLet (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XIf (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XCase (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitTuple (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSectionR (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XSectionL (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XPar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XNegApp (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XAppTypeE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XApp (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLamCase (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLam (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XLitE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XOverLitE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XIPVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XOverLabel (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecFld (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XConLikeOut (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XUnboundVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type XXRoleAnnotDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRoleAnnotDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXAnnDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsAnnotation (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXWarnDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XWarning (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXWarnDecls (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XWarnings (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXRuleBndr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XRuleBndrSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRuleBndr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXRuleDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXRuleDecls (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCRuleDecls (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXForeignDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXDefaultDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCDefaultDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXDerivDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCDerivDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXInstDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XTyFamInstD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataFamInstD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XClsInstD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXClsInstDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCClsInstDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXConDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XConDeclH98 (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XConDeclGADT (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsDerivingClause (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCHsDerivingClause (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsDataDefn (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCHsDataDefn (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXFamilyDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCFamilyDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXFamilyResultSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XTyVarSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCKindSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XNoSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXTyClGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCTyClGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXTyClDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XFamDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXSpliceDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XSpliceDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XCHsGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXHsDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XRoleAnnotD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XDocD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XSpliceD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XRuleD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XAnnD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XWarningD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XForD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XDefD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XKindSigD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XSigD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XValD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XDerivD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XInstD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XTyClD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type XStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type XXFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XCompleteMatchSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XSCCFunSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XMinimalSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

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 XInlineSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XFixSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XIdSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XClassOpSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPatSynSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XTypeSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XCIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXHsIPBinds (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XXABExport (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type XABE (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type Body (PatBuilder GhcPs) Source # 
Instance details

Defined in RdrHsSyn

type InfixOp (PatBuilder GhcPs) Source # 
Instance details

Defined in RdrHsSyn

type FunArg (PatBuilder GhcPs) Source # 
Instance details

Defined in RdrHsSyn

type XXHsWildCardBndrs (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Types

type XXHsImplicitBndrs (GhcPass _1) _2 Source # 
Instance details

Defined in GHC.Hs.Types

type XXGRHS (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHS (GhcPass _) b = NoExtCon
type XCGRHS (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHSs (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHSs (GhcPass _) b = NoExtCon
type XCGRHSs (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXMatch (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXMatch (GhcPass _) b = NoExtCon
type XCMatch (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXMatchGroup (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXFamEqn (GhcPass _) r Source # 
Instance details

Defined in GHC.Hs.Decls

type XCFamEqn (GhcPass _) r Source # 
Instance details

Defined in GHC.Hs.Decls

type XPSB (GhcPass idL) GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcTc = NameSet
type XPSB (GhcPass idL) GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn = NameSet
type XPSB (GhcPass idL) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XFunBind (GhcPass pL) GhcTc 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) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type XRec (GhcPass p) f Source # 
Instance details

Defined in GHC.Hs.Extension

type XRec (GhcPass p) f = Located (f (GhcPass p))
type XRecStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _) GhcTc b = Type
type XParStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmtBlock (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 XXHsBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XPatSynBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type XAbsBinds (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 XXValBindsLR (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 XXHsLocalBindsLR (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 XXStmtLR (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXStmtLR (GhcPass _1) (GhcPass _2) b = NoExtCon
type XLetStmt (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XLetStmt (GhcPass _1) (GhcPass _2) b = NoExtField
type XLastStmt (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XLastStmt (GhcPass _1) (GhcPass _2) b = NoExtField

data Pass Source #

Constructors

Parsed 
Renamed 
Typechecked 
Instances
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 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pass #

toConstr :: Pass -> Constr #

dataTypeOf :: Pass -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pass) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pass) #

gmapT :: (forall b. Data b => b -> b) -> Pass -> Pass #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pass -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pass -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pass -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pass -> m Pass #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pass -> m Pass #

type family XRec p (f :: * -> *) = 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
type XRec (GhcPass p) f Source # 
Instance details

Defined in GHC.Hs.Extension

type XRec (GhcPass p) f = Located (f (GhcPass p))

type family IdP p Source #

Maps the "normal" id type for a given pass

Instances
type IdP GhcTc Source # 
Instance details

Defined in GHC.Hs.Extension

type IdP GhcTc = Id
type IdP GhcRn Source # 
Instance details

Defined in GHC.Hs.Extension

type IdP GhcRn = Name
type IdP GhcPs Source # 
Instance details

Defined in GHC.Hs.Extension

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.

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
type XHsValBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XHsIPBinds x x' Source #

Instances
type XHsIPBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XEmptyLocalBinds x x' Source #

Instances
type XEmptyLocalBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsLocalBindsLR x x' Source #

Instances
type XXHsLocalBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXHsLocalBindsLR (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XHsValBinds x x'), c (XHsIPBinds x x'), c (XEmptyLocalBinds x x'), c (XXHsLocalBindsLR x x')) Source #

type family XValBinds x x' Source #

Instances
type XValBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXValBindsLR x x' Source #

Instances
type XXValBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXValBindsLR (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XValBinds x x'), c (XXValBindsLR x x')) Source #

type family XFunBind x x' Source #

Instances
type XFunBind (GhcPass pL) GhcTc 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) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPatBind x x' Source #

Instances
type XPatBind GhcTc (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 GhcPs (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XVarBind x x' Source #

Instances
type XVarBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XAbsBinds x x' Source #

Instances
type XAbsBinds (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPatSynBind x x' Source #

Instances
type XPatSynBind (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsBindsLR x x' Source #

Instances
type XXHsBindsLR (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXHsBindsLR (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XFunBind x x'), c (XPatBind x x'), c (XVarBind x x'), c (XAbsBinds x x'), c (XPatSynBind x x'), c (XXHsBindsLR x x')) Source #

type family XABE x Source #

Instances
type XABE (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXABExport x Source #

Instances
type XXABExport (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXABExport (c :: * -> Constraint) (x :: *) = (c (XABE x), c (XXABExport x)) Source #

type family XPSB x x' Source #

Instances
type XPSB (GhcPass idL) GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcTc = NameSet
type XPSB (GhcPass idL) GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XPSB (GhcPass idL) GhcRn = NameSet
type XPSB (GhcPass idL) GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXPatSynBind x x' Source #

Instances
type XXPatSynBind (GhcPass idL) (GhcPass idR) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXPatSynBind (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XPSB x x'), c (XXPatSynBind x x')) Source #

type family XIPBinds x Source #

Instances
type XIPBinds GhcTc Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcRn Source # 
Instance details

Defined in GHC.Hs.Binds

type XIPBinds GhcPs Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXHsIPBinds x Source #

Instances
type XXHsIPBinds (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXHsIPBinds (c :: * -> Constraint) (x :: *) = (c (XIPBinds x), c (XXHsIPBinds x)) Source #

type family XCIPBind x Source #

Instances
type XCIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXIPBind x Source #

Instances
type XXIPBind (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXIPBind (c :: * -> Constraint) (x :: *) = (c (XCIPBind x), c (XXIPBind x)) Source #

type family XTypeSig x Source #

Instances
type XTypeSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XPatSynSig x Source #

Instances
type XPatSynSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XClassOpSig x Source #

Instances
type XClassOpSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XIdSig x Source #

Instances
type XIdSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XFixSig x Source #

Instances
type XFixSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XInlineSig x Source #

Instances
type XInlineSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSpecSig x Source #

Instances
type XSpecSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSpecInstSig x Source #

Instances
type XSpecInstSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XMinimalSig x Source #

Instances
type XMinimalSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XSCCFunSig x Source #

Instances
type XSCCFunSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XCompleteMatchSig x Source #

Instances
type XCompleteMatchSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXSig x Source #

Instances
type XXSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXSig (c :: * -> Constraint) (x :: *) = (c (XTypeSig x), c (XPatSynSig x), c (XClassOpSig x), c (XIdSig x), c (XFixSig x), c (XInlineSig x), c (XSpecSig x), c (XSpecInstSig x), c (XMinimalSig x), c (XSCCFunSig x), c (XCompleteMatchSig x), c (XXSig x)) Source #

type family XFixitySig x Source #

Instances
type XFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type family XXFixitySig x Source #

Instances
type XXFixitySig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Binds

type ForallXFixitySig (c :: * -> Constraint) (x :: *) = (c (XFixitySig x), c (XXFixitySig x)) Source #

type family XStandaloneKindSig x Source #

Instances
type XStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXStandaloneKindSig x Source #

Instances
type XXStandaloneKindSig (GhcPass p) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyClD x Source #

Instances
type XTyClD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XInstD x Source #

Instances
type XInstD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDerivD x Source #

Instances
type XDerivD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XValD x Source #

Instances
type XValD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSigD x Source #

Instances
type XSigD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XKindSigD x Source #

Instances
type XKindSigD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDefD x Source #

Instances
type XDefD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XForD x Source #

Instances
type XForD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XWarningD x Source #

Instances
type XWarningD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XAnnD x Source #

Instances
type XAnnD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRuleD x Source #

Instances
type XRuleD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSpliceD x Source #

Instances
type XSpliceD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDocD x Source #

Instances
type XDocD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRoleAnnotD x Source #

Instances
type XRoleAnnotD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDecl x Source #

Instances
type XXHsDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXHsDecl (c :: * -> Constraint) (x :: *) = (c (XTyClD x), c (XInstD x), c (XDerivD x), c (XValD x), c (XSigD x), c (XKindSigD x), c (XDefD x), c (XForD x), c (XWarningD x), c (XAnnD x), c (XRuleD x), c (XSpliceD x), c (XDocD x), c (XRoleAnnotD x), c (XXHsDecl x)) Source #

type family XCHsGroup x Source #

Instances
type XCHsGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsGroup x Source #

Instances
type XXHsGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXHsGroup (c :: * -> Constraint) (x :: *) = (c (XCHsGroup x), c (XXHsGroup x)) Source #

type family XSpliceDecl x Source #

Instances
type XSpliceDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXSpliceDecl x Source #

Instances
type XXSpliceDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXSpliceDecl (c :: * -> Constraint) (x :: *) = (c (XSpliceDecl x), c (XXSpliceDecl x)) Source #

type family XFamDecl x Source #

Instances
type XFamDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XSynDecl x Source #

Instances
type XSynDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XSynDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDataDecl x Source #

Instances
type XDataDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XDataDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type family XClassDecl x Source #

Instances
type XClassDecl GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XClassDecl GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXTyClDecl x Source #

Instances
type XXTyClDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXTyClDecl (c :: * -> Constraint) (x :: *) = (c (XFamDecl x), c (XSynDecl x), c (XDataDecl x), c (XClassDecl x), c (XXTyClDecl x)) Source #

type family XCTyClGroup x Source #

Instances
type XCTyClGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXTyClGroup x Source #

Instances
type XXTyClGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXTyClGroup (c :: * -> Constraint) (x :: *) = (c (XCTyClGroup x), c (XXTyClGroup x)) Source #

type family XNoSig x Source #

Instances
type XNoSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCKindSig x Source #

Instances
type XCKindSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyVarSig x Source #

Instances
type XTyVarSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFamilyResultSig x Source #

Instances
type XXFamilyResultSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXFamilyResultSig (c :: * -> Constraint) (x :: *) = (c (XNoSig x), c (XCKindSig x), c (XTyVarSig x), c (XXFamilyResultSig x)) Source #

type family XCFamilyDecl x Source #

Instances
type XCFamilyDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFamilyDecl x Source #

Instances
type XXFamilyDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXFamilyDecl (c :: * -> Constraint) (x :: *) = (c (XCFamilyDecl x), c (XXFamilyDecl x)) Source #

type family XCHsDataDefn x Source #

Instances
type XCHsDataDefn (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDataDefn x Source #

Instances
type XXHsDataDefn (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXHsDataDefn (c :: * -> Constraint) (x :: *) = (c (XCHsDataDefn x), c (XXHsDataDefn x)) Source #

type family XCHsDerivingClause x Source #

Instances
type XCHsDerivingClause (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXHsDerivingClause x Source #

Instances
type XXHsDerivingClause (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XConDeclGADT x Source #

Instances
type XConDeclGADT (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XConDeclH98 x Source #

Instances
type XConDeclH98 (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXConDecl x Source #

Instances
type XXConDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXConDecl (c :: * -> Constraint) (x :: *) = (c (XConDeclGADT x), c (XConDeclH98 x), c (XXConDecl x)) Source #

type family XCFamEqn x r Source #

Instances
type XCFamEqn (GhcPass _) r Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXFamEqn x r Source #

Instances
type XXFamEqn (GhcPass _) r Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXFamEqn (c :: * -> Constraint) (x :: *) (r :: *) = (c (XCFamEqn x r), c (XXFamEqn x r)) Source #

type family XCClsInstDecl x Source #

Instances
type XCClsInstDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXClsInstDecl x Source #

Instances
type XXClsInstDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXClsInstDecl (c :: * -> Constraint) (x :: *) = (c (XCClsInstDecl x), c (XXClsInstDecl x)) Source #

type family XClsInstD x Source #

Instances
type XClsInstD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XDataFamInstD x Source #

Instances
type XDataFamInstD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XTyFamInstD x Source #

Instances
type XTyFamInstD (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXInstDecl x Source #

Instances
type XXInstDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXInstDecl (c :: * -> Constraint) (x :: *) = (c (XClsInstD x), c (XDataFamInstD x), c (XTyFamInstD x), c (XXInstDecl x)) Source #

type family XCDerivDecl x Source #

Instances
type XCDerivDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXDerivDecl x Source #

Instances
type XXDerivDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXDerivDecl (c :: * -> Constraint) (x :: *) = (c (XCDerivDecl x), c (XXDerivDecl x)) Source #

type family XViaStrategy x Source #

Instances
type XViaStrategy GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XViaStrategy GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type family XCDefaultDecl x Source #

Instances
type XCDefaultDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXDefaultDecl x Source #

Instances
type XXDefaultDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXDefaultDecl (c :: * -> Constraint) (x :: *) = (c (XCDefaultDecl x), c (XXDefaultDecl x)) Source #

type family XForeignImport x Source #

Instances
type XForeignImport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignImport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type family XForeignExport x Source #

Instances
type XForeignExport GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XForeignExport GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXForeignDecl x Source #

Instances
type XXForeignDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXForeignDecl (c :: * -> Constraint) (x :: *) = (c (XForeignImport x), c (XForeignExport x), c (XXForeignDecl x)) Source #

type family XCRuleDecls x Source #

Instances
type XCRuleDecls (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleDecls x Source #

Instances
type XXRuleDecls (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXRuleDecls (c :: * -> Constraint) (x :: *) = (c (XCRuleDecls x), c (XXRuleDecls x)) Source #

type family XHsRule x Source #

Instances
type XHsRule GhcTc Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcRn Source # 
Instance details

Defined in GHC.Hs.Decls

type XHsRule GhcPs Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleDecl x Source #

Instances
type XXRuleDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXRuleDecl (c :: * -> Constraint) (x :: *) = (c (XHsRule x), c (XXRuleDecl x)) Source #

type family XCRuleBndr x Source #

Instances
type XCRuleBndr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XRuleBndrSig x Source #

Instances
type XRuleBndrSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRuleBndr x Source #

Instances
type XXRuleBndr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXRuleBndr (c :: * -> Constraint) (x :: *) = (c (XCRuleBndr x), c (XRuleBndrSig x), c (XXRuleBndr x)) Source #

type family XWarnings x Source #

Instances
type XWarnings (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXWarnDecls x Source #

Instances
type XXWarnDecls (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXWarnDecls (c :: * -> Constraint) (x :: *) = (c (XWarnings x), c (XXWarnDecls x)) Source #

type family XWarning x Source #

Instances
type XWarning (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXWarnDecl x Source #

Instances
type XXWarnDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXWarnDecl (c :: * -> Constraint) (x :: *) = (c (XWarning x), c (XXWarnDecl x)) Source #

type family XHsAnnotation x Source #

Instances
type XHsAnnotation (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXAnnDecl x Source #

Instances
type XXAnnDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXAnnDecl (c :: * -> Constraint) (x :: *) = (c (XHsAnnotation x), c (XXAnnDecl x)) Source #

type family XCRoleAnnotDecl x Source #

Instances
type XCRoleAnnotDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type family XXRoleAnnotDecl x Source #

Instances
type XXRoleAnnotDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Decls

type ForallXRoleAnnotDecl (c :: * -> Constraint) (x :: *) = (c (XCRoleAnnotDecl x), c (XXRoleAnnotDecl x)) Source #

type family XVar x Source #

Instances
type XVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XUnboundVar x Source #

Instances
type XUnboundVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XConLikeOut x Source #

Instances
type XConLikeOut (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecFld x Source #

Instances
type XRecFld (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOverLabel x Source #

Instances
type XOverLabel (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XIPVar x Source #

Instances
type XIPVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOverLitE x Source #

Instances
type XOverLitE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLitE x Source #

Instances
type XLitE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLam x Source #

Instances
type XLam (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLamCase x Source #

Instances
type XLamCase (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApp x Source #

Instances
type XApp (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XAppTypeE x Source #

Instances
type XAppTypeE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XOpApp x Source #

Instances
type XOpApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XOpApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XNegApp x Source #

Instances
type XNegApp (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XPar x Source #

Instances
type XPar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSectionL x Source #

Instances
type XSectionL (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSectionR x Source #

Instances
type XSectionR (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitTuple x Source #

Instances
type XExplicitTuple (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitSum x Source #

Instances
type XExplicitSum GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitSum GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCase x Source #

Instances
type XCase (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XIf x Source #

Instances
type XIf (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XMultiIf x Source #

Instances
type XMultiIf GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMultiIf GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLet x Source #

Instances
type XLet (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XDo x Source #

Instances
type XDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcTc = Type
type XDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExplicitList x Source #

Instances
type XExplicitList GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XExplicitList GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecordCon x Source #

Instances
type XRecordCon GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordCon GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecordUpd x Source #

Instances
type XRecordUpd GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecordUpd GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XExprWithTySig x Source #

Instances
type XExprWithTySig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XArithSeq x Source #

Instances
type XArithSeq GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XArithSeq GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSCC x Source #

Instances
type XSCC (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCoreAnn x Source #

Instances
type XCoreAnn (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XBracket x Source #

Instances
type XBracket (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRnBracketOut x Source #

Instances
type XRnBracketOut (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTcBracketOut x Source #

Instances
type XTcBracketOut (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSpliceE x Source #

Instances
type XSpliceE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XProc x Source #

Instances
type XProc (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XStatic x Source #

Instances
type XStatic GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XStatic GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTick x Source #

Instances
type XTick (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XBinTick x Source #

Instances
type XBinTick (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTickPragma x Source #

Instances
type XTickPragma (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XWrap x Source #

Instances
type XWrap (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXExpr x Source #

Instances
type XXExpr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type ForallXExpr (c :: * -> Constraint) (x :: *) = (c (XVar x), c (XUnboundVar x), c (XConLikeOut x), c (XRecFld x), c (XOverLabel x), c (XIPVar x), c (XOverLitE x), c (XLitE x), c (XLam x), c (XLamCase x), c (XApp x), c (XAppTypeE x), c (XOpApp x), c (XNegApp x), c (XPar x), c (XSectionL x), c (XSectionR x), c (XExplicitTuple x), c (XExplicitSum x), c (XCase x), c (XIf x), c (XMultiIf x), c (XLet x), c (XDo x), c (XExplicitList x), c (XRecordCon x), c (XRecordUpd x), c (XExprWithTySig x), c (XArithSeq x), c (XSCC x), c (XCoreAnn x), c (XBracket x), c (XRnBracketOut x), c (XTcBracketOut x), c (XSpliceE x), c (XProc x), c (XStatic x), c (XTick x), c (XBinTick x), c (XTickPragma x), c (XWrap x), c (XXExpr x)) Source #

type family XUnambiguous x Source #

Instances
type XUnambiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XUnambiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XUnambiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type family XAmbiguous x Source #

Instances
type XAmbiguous GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XAmbiguous GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XAmbiguous GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type family XXAmbiguousFieldOcc x Source #

Instances
type XXAmbiguousFieldOcc (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type ForallXAmbiguousFieldOcc (c :: * -> Constraint) (x :: *) = (c (XUnambiguous x), c (XAmbiguous x), c (XXAmbiguousFieldOcc x)) Source #

type family XPresent x Source #

Instances
type XPresent (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XMissing x Source #

Instances
type XMissing GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XMissing GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXTupArg x Source #

Instances
type XXTupArg (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type ForallXTupArg (c :: * -> Constraint) (x :: *) = (c (XPresent x), c (XMissing x), c (XXTupArg x)) Source #

type family XTypedSplice x Source #

Instances
type XTypedSplice (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XUntypedSplice x Source #

Instances
type XUntypedSplice (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XQuasiQuote x Source #

Instances
type XQuasiQuote (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XSpliced x Source #

Instances
type XSpliced (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXSplice x Source #

Instances
type XXSplice (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type ForallXSplice (c :: * -> Constraint) (x :: *) = (c (XTypedSplice x), c (XUntypedSplice x), c (XQuasiQuote x), c (XSpliced x), c (XXSplice x)) Source #

type family XExpBr x Source #

Instances
type XExpBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XPatBr x Source #

Instances
type XPatBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XDecBrL x Source #

Instances
type XDecBrL (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XDecBrG x Source #

Instances
type XDecBrG (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTypBr x Source #

Instances
type XTypBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XVarBr x Source #

Instances
type XVarBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTExpBr x Source #

Instances
type XTExpBr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXBracket x Source #

Instances
type XXBracket (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type ForallXBracket (c :: * -> Constraint) (x :: *) = (c (XExpBr x), c (XPatBr x), c (XDecBrL x), c (XDecBrG x), c (XTypBr x), c (XVarBr x), c (XTExpBr x), c (XXBracket x)) Source #

type family XCmdTop x Source #

Instances
type XCmdTop GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdTop GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXCmdTop x Source #

Instances
type XXCmdTop (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type ForallXCmdTop (c :: * -> Constraint) (x :: *) = (c (XCmdTop x), c (XXCmdTop x)) Source #

type family XMG x b Source #

Instances
type XMG GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XMG GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXMatchGroup x b Source #

Instances
type XXMatchGroup (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type ForallXMatchGroup (c :: * -> Constraint) (x :: *) (b :: *) = (c (XMG x b), c (XXMatchGroup x b)) Source #

type family XCMatch x b Source #

Instances
type XCMatch (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXMatch x b Source #

Instances
type XXMatch (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXMatch (GhcPass _) b = NoExtCon

type ForallXMatch (c :: * -> Constraint) (x :: *) (b :: *) = (c (XCMatch x b), c (XXMatch x b)) Source #

type family XCGRHSs x b Source #

Instances
type XCGRHSs (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXGRHSs x b Source #

Instances
type XXGRHSs (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHSs (GhcPass _) b = NoExtCon

type ForallXGRHSs (c :: * -> Constraint) (x :: *) (b :: *) = (c (XCGRHSs x b), c (XXGRHSs x b)) Source #

type family XCGRHS x b Source #

Instances
type XCGRHS (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXGRHS x b Source #

Instances
type XXGRHS (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXGRHS (GhcPass _) b = NoExtCon

type ForallXGRHS (c :: * -> Constraint) (x :: *) (b :: *) = (c (XCGRHS x b), c (XXGRHS x b)) Source #

type family XLastStmt x x' b Source #

Instances
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
type XBindStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBindStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeStmt x x' b Source #

Instances
type XApplicativeStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XApplicativeStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XBodyStmt x x' b Source #

Instances
type XBodyStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XBodyStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XLetStmt x x' b Source #

Instances
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
type XParStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _) GhcTc b = Type
type XParStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XParStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XTransStmt x x' b Source #

Instances
type XTransStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XTransStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XRecStmt x x' b Source #

Instances
type XRecStmt (GhcPass _) GhcRn b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _) GhcPs b Source # 
Instance details

Defined in GHC.Hs.Expr

type XRecStmt (GhcPass _) GhcTc b Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXStmtLR x x' b Source #

Instances
type XXStmtLR (GhcPass _1) (GhcPass _2) b Source # 
Instance details

Defined in GHC.Hs.Expr

type XXStmtLR (GhcPass _1) (GhcPass _2) b = NoExtCon

type ForallXStmtLR (c :: * -> Constraint) (x :: *) (x' :: *) (b :: *) = (c (XLastStmt x x' b), c (XBindStmt x x' b), c (XApplicativeStmt x x' b), c (XBodyStmt x x' b), c (XLetStmt x x' b), c (XParStmt x x' b), c (XTransStmt x x' b), c (XRecStmt x x' b), c (XXStmtLR x x' b)) Source #

type family XCmdArrApp x Source #

Instances
type XCmdArrApp GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdArrApp GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdArrForm x Source #

Instances
type XCmdArrForm (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdApp x Source #

Instances
type XCmdApp (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLam x Source #

Instances
type XCmdLam (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdPar x Source #

Instances
type XCmdPar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdCase x Source #

Instances
type XCmdCase (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdIf x Source #

Instances
type XCmdIf (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdLet x Source #

Instances
type XCmdLet (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdDo x Source #

Instances
type XCmdDo GhcTc Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcRn Source # 
Instance details

Defined in GHC.Hs.Expr

type XCmdDo GhcPs Source # 
Instance details

Defined in GHC.Hs.Expr

type family XCmdWrap x Source #

Instances
type XCmdWrap (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXCmd x Source #

Instances
type XXCmd (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type ForallXCmd (c :: * -> Constraint) (x :: *) = (c (XCmdArrApp x), c (XCmdArrForm x), c (XCmdApp x), c (XCmdLam x), c (XCmdPar x), c (XCmdCase x), c (XCmdIf x), c (XCmdLet x), c (XCmdDo x), c (XCmdWrap x), c (XXCmd x)) Source #

type family XParStmtBlock x x' Source #

Instances
type XParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXParStmtBlock x x' Source #

Instances
type XXParStmtBlock (GhcPass pL) (GhcPass pR) Source # 
Instance details

Defined in GHC.Hs.Expr

type ForallXParStmtBlock (c :: * -> Constraint) (x :: *) (x' :: *) = (c (XParStmtBlock x x'), c (XXParStmtBlock x x')) Source #

type family XApplicativeArgOne x Source #

Instances
type XApplicativeArgOne (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XApplicativeArgMany x Source #

Instances
type XApplicativeArgMany (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XXApplicativeArg x Source #

Instances
type XXApplicativeArg (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Expr

type family XHsChar x Source #

Instances
type XHsChar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsCharPrim x Source #

Instances
type XHsCharPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsString x Source #

Instances
type XHsString (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsStringPrim x Source #

Instances
type XHsStringPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInt x Source #

Instances
type XHsInt (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsIntPrim x Source #

Instances
type XHsIntPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsWordPrim x Source #

Instances
type XHsWordPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInt64Prim x Source #

Instances
type XHsInt64Prim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsWord64Prim x Source #

Instances
type XHsWord64Prim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsInteger x Source #

Instances
type XHsInteger (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsRat x Source #

Instances
type XHsRat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsFloatPrim x Source #

Instances
type XHsFloatPrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XHsDoublePrim x Source #

Instances
type XHsDoublePrim (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type family XXLit x Source #

Instances
type XXLit (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type ForallXHsLit (c :: * -> Constraint) (x :: *) = (c (XHsChar x), c (XHsCharPrim x), c (XHsDoublePrim x), c (XHsFloatPrim x), c (XHsInt x), c (XHsInt64Prim x), c (XHsIntPrim x), c (XHsInteger x), c (XHsRat x), c (XHsString x), c (XHsStringPrim x), c (XHsWord64Prim x), c (XHsWordPrim x), c (XXLit x)) Source #

Helper to apply a constraint to all extension points. It has one entry per extension point type family.

type family XOverLit x Source #

Instances
type XOverLit GhcTc Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcRn Source # 
Instance details

Defined in GHC.Hs.Lit

type XOverLit GhcPs Source # 
Instance details

Defined in GHC.Hs.Lit

type family XXOverLit x Source #

Instances
type XXOverLit (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Lit

type ForallXOverLit (c :: * -> Constraint) (x :: *) = (c (XOverLit x), c (XXOverLit x)) Source #

type family XWildPat x Source #

Instances
type XWildPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XWildPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type family XVarPat x Source #

Instances
type XVarPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XLazyPat x Source #

Instances
type XLazyPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XAsPat x Source #

Instances
type XAsPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XParPat x Source #

Instances
type XParPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XBangPat x Source #

Instances
type XBangPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XListPat x Source #

Instances
type XListPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XListPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type family XTuplePat x Source #

Instances
type XTuplePat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XTuplePat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSumPat x Source #

Instances
type XSumPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcTc = [Type]
type XSumPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSumPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type family XConPat x Source #

type family XViewPat x Source #

Instances
type XViewPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XViewPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSplicePat x Source #

Instances
type XSplicePat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XLitPat x Source #

Instances
type XLitPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XNPat x Source #

Instances
type XNPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type family XNPlusKPat x Source #

Instances
type XNPlusKPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XNPlusKPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type family XSigPat x Source #

Instances
type XSigPat GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XSigPat GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type family XCoPat x Source #

Instances
type XCoPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type family XXPat x Source #

Instances
type XXPat (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Pat

type ForallXPat (c :: * -> Constraint) (x :: *) = (c (XWildPat x), c (XVarPat x), c (XLazyPat x), c (XAsPat x), c (XParPat x), c (XBangPat x), c (XListPat x), c (XTuplePat x), c (XSumPat x), c (XViewPat x), c (XSplicePat x), c (XLitPat x), c (XNPat x), c (XNPlusKPat x), c (XSigPat x), c (XCoPat x), c (XXPat x)) Source #

type family XHsQTvs x Source #

Instances
type XHsQTvs GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XHsQTvs GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XHsQTvs GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type family XXLHsQTyVars x Source #

Instances
type XXLHsQTyVars (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type ForallXLHsQTyVars (c :: * -> Constraint) (x :: *) = (c (XHsQTvs x), c (XXLHsQTyVars x)) Source #

type family XHsIB x b Source #

Instances
type XHsIB GhcTc _ Source # 
Instance details

Defined in GHC.Hs.Types

type XHsIB GhcTc _ = [Name]
type XHsIB GhcRn _ Source # 
Instance details

Defined in GHC.Hs.Types

type XHsIB GhcRn _ = [Name]
type XHsIB GhcPs _ Source # 
Instance details

Defined in GHC.Hs.Types

type family XXHsImplicitBndrs x b Source #

Instances
type XXHsImplicitBndrs (GhcPass _1) _2 Source # 
Instance details

Defined in GHC.Hs.Types

type ForallXHsImplicitBndrs (c :: * -> Constraint) (x :: *) (b :: *) = (c (XHsIB x b), c (XXHsImplicitBndrs x b)) Source #

type family XHsWC x b Source #

Instances
type XHsWC GhcTc b Source # 
Instance details

Defined in GHC.Hs.Types

type XHsWC GhcTc b = [Name]
type XHsWC GhcRn b Source # 
Instance details

Defined in GHC.Hs.Types

type XHsWC GhcRn b = [Name]
type XHsWC GhcPs b Source # 
Instance details

Defined in GHC.Hs.Types

type family XXHsWildCardBndrs x b Source #

Instances
type XXHsWildCardBndrs (GhcPass _) b Source # 
Instance details

Defined in GHC.Hs.Types

type ForallXHsWildCardBndrs (c :: * -> Constraint) (x :: *) (b :: *) = (c (XHsWC x b), c (XXHsWildCardBndrs x b)) Source #

type family XForAllTy x Source #

Instances
type XForAllTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XQualTy x Source #

Instances
type XQualTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XTyVar x Source #

Instances
type XTyVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XAppTy x Source #

Instances
type XAppTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XAppKindTy x Source #

Instances
type XAppKindTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XFunTy x Source #

Instances
type XFunTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XListTy x Source #

Instances
type XListTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XTupleTy x Source #

Instances
type XTupleTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XSumTy x Source #

Instances
type XSumTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XOpTy x Source #

Instances
type XOpTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XParTy x Source #

Instances
type XParTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XIParamTy x Source #

Instances
type XIParamTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XStarTy x Source #

Instances
type XStarTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XKindSig x Source #

Instances
type XKindSig (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XSpliceTy x Source #

Instances
type XSpliceTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XSpliceTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XSpliceTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type family XDocTy x Source #

Instances
type XDocTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XBangTy x Source #

Instances
type XBangTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XRecTy x Source #

Instances
type XRecTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XExplicitListTy x Source #

Instances
type XExplicitListTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitListTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitListTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type family XExplicitTupleTy x Source #

Instances
type XExplicitTupleTy GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitTupleTy GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XExplicitTupleTy GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type family XTyLit x Source #

Instances
type XTyLit (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XWildCardTy x Source #

Instances
type XWildCardTy (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XXType x Source #

Instances
type XXType (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type ForallXType (c :: * -> Constraint) (x :: *) = (c (XForAllTy x), c (XQualTy x), c (XTyVar x), c (XAppTy x), c (XAppKindTy x), c (XFunTy x), c (XListTy x), c (XTupleTy x), c (XSumTy x), c (XOpTy x), c (XParTy x), c (XIParamTy x), c (XStarTy x), c (XKindSig x), c (XSpliceTy x), c (XDocTy x), c (XBangTy x), c (XRecTy x), c (XExplicitListTy x), c (XExplicitTupleTy x), c (XTyLit x), c (XWildCardTy x), c (XXType x)) Source #

Helper to apply a constraint to all extension points. It has one entry per extension point type family.

type family XUserTyVar x Source #

Instances
type XUserTyVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XKindedTyVar x Source #

Instances
type XKindedTyVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XXTyVarBndr x Source #

Instances
type XXTyVarBndr (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type ForallXTyVarBndr (c :: * -> Constraint) (x :: *) = (c (XUserTyVar x), c (XKindedTyVar x), c (XXTyVarBndr x)) Source #

type family XConDeclField x Source #

Instances
type XConDeclField (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type family XXConDeclField x Source #

Instances
type XXConDeclField (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type ForallXConDeclField (c :: * -> Constraint) (x :: *) = (c (XConDeclField x), c (XXConDeclField x)) Source #

type family XCFieldOcc x Source #

Instances
type XCFieldOcc GhcTc Source # 
Instance details

Defined in GHC.Hs.Types

type XCFieldOcc GhcRn Source # 
Instance details

Defined in GHC.Hs.Types

type XCFieldOcc GhcPs Source # 
Instance details

Defined in GHC.Hs.Types

type family XXFieldOcc x Source #

Instances
type XXFieldOcc (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.Types

type ForallXFieldOcc (c :: * -> Constraint) (x :: *) = (c (XCFieldOcc x), c (XXFieldOcc x)) Source #

type family XCImportDecl x Source #

Instances
type XCImportDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XXImportDecl x Source #

Instances
type XXImportDecl (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type ForallXImportDecl (c :: * -> Constraint) (x :: *) = (c (XCImportDecl x), c (XXImportDecl x)) Source #

type family XIEVar x Source #

Instances
type XIEVar (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingAbs x Source #

Instances
type XIEThingAbs (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingAll x Source #

Instances
type XIEThingAll (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEThingWith x Source #

Instances
type XIEThingWith (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEModuleContents x Source #

Instances
type XIEModuleContents (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEGroup x Source #

Instances
type XIEGroup (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEDoc x Source #

Instances
type XIEDoc (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XIEDocNamed x Source #

Instances
type XIEDocNamed (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type family XXIE x Source #

Instances
type XXIE (GhcPass _) Source # 
Instance details

Defined in GHC.Hs.ImpExp

type XXIE (GhcPass _) = NoExtCon

type ForallXIE (c :: * -> Constraint) (x :: *) = (c (XIEVar x), c (XIEThingAbs x), c (XIEThingAll x), c (XIEThingWith x), c (XIEModuleContents x), c (XIEGroup x), c (XIEDoc x), c (XIEDocNamed x), c (XXIE x)) Source #

class Convertable a b | a -> b where Source #

Conversion of annotations from one type index to another. This is required where the AST is converted from one pass to another, and the extension values need to be brought along if possible. So for example a SourceText is converted via id, but needs a type signature to keep the type checker happy.

Methods

convert :: a -> b Source #

Instances
Convertable a a Source # 
Instance details

Defined in GHC.Hs.Extension

Methods

convert :: a -> a Source #

type ConvertIdX a b = (XHsDoublePrim a ~ XHsDoublePrim b, XHsFloatPrim a ~ XHsFloatPrim b, XHsRat a ~ XHsRat b, XHsInteger a ~ XHsInteger b, XHsWord64Prim a ~ XHsWord64Prim b, XHsInt64Prim a ~ XHsInt64Prim b, XHsWordPrim a ~ XHsWordPrim b, XHsIntPrim a ~ XHsIntPrim b, XHsInt a ~ XHsInt b, XHsStringPrim a ~ XHsStringPrim b, XHsString a ~ XHsString b, XHsCharPrim a ~ XHsCharPrim b, XHsChar a ~ XHsChar b, XXLit a ~ XXLit b) Source #

A constraint capturing all the extension points that can be converted via instance Convertable a a

type OutputableX p = (Outputable (XIPBinds p), Outputable (XViaStrategy p), Outputable (XViaStrategy GhcRn)) Source #

Provide a summary constraint that gives all am Outputable constraint to extension points needing one

type OutputableBndrId pass = (OutputableBndr (NameOrRdrName (IdP (GhcPass pass))), OutputableBndr (IdP (GhcPass pass)), OutputableBndr (NameOrRdrName (IdP (NoGhcTc (GhcPass pass)))), OutputableBndr (IdP (NoGhcTc (GhcPass pass))), NoGhcTc (GhcPass pass) ~ NoGhcTc (NoGhcTc (GhcPass pass)), OutputableX (GhcPass pass), OutputableX (NoGhcTc (GhcPass pass))) Source #

Constraint type to bundle up the requirement for OutputableBndr on both the p and the NameOrRdrName type for it