ghc-8.4.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsDecls

Contents

Description

Abstract syntax of global declarations.

Definitions for: SynDecl and ConDecl, ClassDecl, InstDecl, DefaultDecl and ForeignDecl.

Synopsis

Toplevel declarations

data HsDecl id Source #

A Haskell Declaration

Constructors

TyClD (TyClDecl id)

Type or Class Declaration

InstD (InstDecl id)

Instance declaration

DerivD (DerivDecl id)

Deriving declaration

ValD (HsBind id)

Value declaration

SigD (Sig id)

Signature declaration

DefD (DefaultDecl id)

'default' declaration

ForD (ForeignDecl id)

Foreign declaration

WarningD (WarnDecls id)

Warning declaration

AnnD (AnnDecl id)

Annotation declaration

RuleD (RuleDecls id)

Rule declaration

VectD (VectDecl id)

Vectorise declaration

SpliceD (SpliceDecl id)

Splice declaration (Includes quasi-quotes)

DocD DocDecl

Documentation comment declaration

RoleAnnotD (RoleAnnotDecl id)

Role annotation declaration

Instances
DataId id => Data (HsDecl id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: HsDecl id -> Constr Source #

dataTypeOf :: HsDecl id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (HsDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: HsDecl pass -> SDoc Source #

pprPrec :: Rational -> HsDecl pass -> SDoc Source #

type LHsDecl id Source #

Arguments

 = Located (HsDecl id)

When in a list this may have

data HsDataDefn pass Source #

Haskell Data type Definition

Constructors

HsDataDefn

Declares a data type or newtype, giving its constructors data/newtype T a = constrs data/newtype instance T [a] = constrs

Fields

Instances
DataId id => Data (HsDataDefn id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: HsDataDefn id -> Constr Source #

dataTypeOf :: HsDataDefn id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (HsDataDefn pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: HsDataDefn pass -> SDoc Source #

pprPrec :: Rational -> HsDataDefn pass -> SDoc Source #

type HsDeriving pass Source #

Arguments

 = Located [LHsDerivingClause pass]

The optional deriving clauses of a data declaration. Clauses is plural because one can specify multiple deriving clauses using the -XDerivingStrategies language extension.

The list of LHsDerivingClauses corresponds to exactly what the user requested to derive, in order. If no deriving clauses were specified, the list is empty.

Haskell Deriving clause

data HsDerivingClause pass Source #

A single deriving clause of a data declaration.

Constructors

HsDerivingClause 

Fields

Instances
DataId id => Data (HsDerivingClause id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: HsDerivingClause id -> Constr Source #

dataTypeOf :: HsDerivingClause id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (HsDerivingClause pass) # 
Instance details

Defined in HsDecls

Class or type declarations

data TyClDecl pass Source #

A type or class declaration.

Constructors

FamDecl
type/data family T :: *->*

Fields

SynDecl

type declaration

Fields

DataDecl

data declaration

Fields

ClassDecl

Fields

Instances
DataId id => Data (TyClDecl id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: TyClDecl id -> Constr Source #

dataTypeOf :: TyClDecl id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (TyClDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: TyClDecl pass -> SDoc Source #

pprPrec :: Rational -> TyClDecl pass -> SDoc Source #

type LTyClDecl pass = Located (TyClDecl pass) Source #

Located Declaration of a Type or Class

data TyClGroup pass Source #

Type or Class Group

Constructors

TyClGroup 

Fields

Instances
DataId id => Data (TyClGroup id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: TyClGroup id -> Constr Source #

dataTypeOf :: TyClGroup id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (TyClGroup pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: TyClGroup pass -> SDoc Source #

pprPrec :: Rational -> TyClGroup pass -> SDoc Source #

mkTyClGroup :: [LTyClDecl pass] -> [LInstDecl pass] -> TyClGroup pass Source #

isClassDecl :: TyClDecl pass -> Bool Source #

type class

isDataDecl :: TyClDecl pass -> Bool Source #

True = argument is a data/newtype declaration.

isSynDecl :: TyClDecl pass -> Bool Source #

type or type instance declaration

tcdName :: TyClDecl pass -> IdP pass Source #

isFamilyDecl :: TyClDecl pass -> Bool Source #

type/data family declaration

isTypeFamilyDecl :: TyClDecl pass -> Bool Source #

type family declaration

isDataFamilyDecl :: TyClDecl pass -> Bool Source #

data family declaration

isOpenTypeFamilyInfo :: FamilyInfo pass -> Bool Source #

open type family info

isClosedTypeFamilyInfo :: FamilyInfo pass -> Bool Source #

closed type family info

hsDeclHasCusk :: TyClDecl GhcRn -> Bool Source #

Does this declaration have a complete, user-supplied kind signature? See Note [Complete user-supplied kind signatures]

famDeclHasCusk Source #

Arguments

:: Maybe Bool

if associated, does the enclosing class have a CUSK?

-> FamilyDecl pass 
-> Bool 

Does this family declaration have a complete, user-supplied kind signature?

data FamilyDecl pass Source #

type Family Declaration

Instances
DataId id => Data (FamilyDecl id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: FamilyDecl id -> Constr Source #

dataTypeOf :: FamilyDecl id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (FamilyDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: FamilyDecl pass -> SDoc Source #

pprPrec :: Rational -> FamilyDecl pass -> SDoc Source #

type LFamilyDecl pass = Located (FamilyDecl pass) Source #

Located type Family Declaration

Instance declarations

data InstDecl pass Source #

Instance Declaration

Constructors

ClsInstD 

Fields

DataFamInstD 

Fields

TyFamInstD 

Fields

Instances
DataId id => Data (InstDecl id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: InstDecl id -> Constr Source #

dataTypeOf :: InstDecl id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (InstDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: InstDecl pass -> SDoc Source #

pprPrec :: Rational -> InstDecl pass -> SDoc Source #

type LInstDecl pass = Located (InstDecl pass) Source #

Located Instance Declaration

data NewOrData Source #

Constructors

NewType
newtype Blah ...
DataType
data Blah ...
Instances
Eq NewOrData # 
Instance details

Defined in HsDecls

Data NewOrData # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: NewOrData -> Constr Source #

dataTypeOf :: NewOrData -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable NewOrData # 
Instance details

Defined in HsDecls

data FamilyInfo pass Source #

Constructors

DataFamily 
OpenTypeFamily 
ClosedTypeFamily (Maybe [LTyFamInstEqn pass])

Nothing if we're in an hs-boot file and the user said "type family Foo x where .."

Instances
DataId pass => Data (FamilyInfo pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: FamilyInfo pass -> Constr Source #

dataTypeOf :: FamilyInfo pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable (FamilyInfo pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: FamilyInfo pass -> SDoc Source #

pprPrec :: Rational -> FamilyInfo pass -> SDoc Source #

newtype TyFamInstDecl pass Source #

Type Family Instance Declaration

Instances
DataId pass => Data (TyFamInstDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: TyFamInstDecl pass -> Constr Source #

dataTypeOf :: TyFamInstDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (TyFamInstDecl pass) # 
Instance details

Defined in HsDecls

type LTyFamInstDecl pass = Located (TyFamInstDecl pass) Source #

Located Type Family Instance Declaration

newtype DataFamInstDecl pass Source #

Data Family Instance Declaration

Instances
DataId pass => Data (DataFamInstDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: DataFamInstDecl pass -> Constr Source #

dataTypeOf :: DataFamInstDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (DataFamInstDecl pass) # 
Instance details

Defined in HsDecls

type LDataFamInstDecl pass = Located (DataFamInstDecl pass) Source #

Located Data Family Instance Declaration

pprFamInstLHS :: (SourceTextX pass, OutputableBndrId pass) => Located (IdP pass) -> HsTyPats pass -> LexicalFixity -> HsContext pass -> Maybe (LHsKind pass) -> SDoc Source #

type FamInstEqn pass rhs Source #

Arguments

 = HsImplicitBndrs pass (FamEqn pass (HsTyPats pass) rhs)

Here, the pats are type patterns (with kind and type bndrs). See Note [Family instance declaration binders]

Family Instance Equation

type LFamInstEqn pass rhs = Located (FamInstEqn pass rhs) Source #

Located Family Instance Equation

data FamEqn pass pats rhs Source #

Family Equation

One equation in a type family instance declaration, data family instance declaration, or type family default. See Note [Type family instance declarations in HsSyn] See Note [Family instance declaration binders]

Constructors

FamEqn

Fields

Instances
(DataId pass, Data pats, Data rhs) => Data (FamEqn pass pats rhs) # 
Instance details

Defined in HsDecls

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FamEqn pass pats rhs -> c (FamEqn pass pats rhs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FamEqn pass pats rhs) Source #

toConstr :: FamEqn pass pats rhs -> Constr Source #

dataTypeOf :: FamEqn pass pats rhs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FamEqn pass pats rhs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FamEqn pass pats rhs)) Source #

gmapT :: (forall b. Data b => b -> b) -> FamEqn pass pats rhs -> FamEqn pass pats rhs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn pass pats rhs -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FamEqn pass pats rhs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> FamEqn pass pats rhs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FamEqn pass pats rhs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FamEqn pass pats rhs -> m (FamEqn pass pats rhs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn pass pats rhs -> m (FamEqn pass pats rhs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FamEqn pass pats rhs -> m (FamEqn pass pats rhs) Source #

type TyFamInstEqn pass = FamInstEqn pass (LHsType pass) Source #

Type Family Instance Equation

type LTyFamInstEqn pass Source #

Arguments

 = Located (TyFamInstEqn pass)

May have AnnKeywordId : AnnSemi when in a list

Located Type Family Instance Equation

type TyFamDefltEqn pass = FamEqn pass (LHsQTyVars pass) (LHsType pass) Source #

Type Family Default Equation

type LTyFamDefltEqn pass = Located (TyFamDefltEqn pass) Source #

Located Type Family Default Equation

type HsTyPats pass = [LHsType pass] Source #

Haskell Type Patterns

type LClsInstDecl pass = Located (ClsInstDecl pass) Source #

Located Class Instance Declaration

data ClsInstDecl pass Source #

Class Instance Declaration

Instances
DataId id => Data (ClsInstDecl id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: ClsInstDecl id -> Constr Source #

dataTypeOf :: ClsInstDecl id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (ClsInstDecl pass) # 
Instance details

Defined in HsDecls

Standalone deriving declarations

data DerivDecl pass Source #

Deriving Declaration

Instances
DataId pass => Data (DerivDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: DerivDecl pass -> Constr Source #

dataTypeOf :: DerivDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (DerivDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: DerivDecl pass -> SDoc Source #

pprPrec :: Rational -> DerivDecl pass -> SDoc Source #

type LDerivDecl pass = Located (DerivDecl pass) Source #

Located Deriving Declaration

RULE declarations

type LRuleDecls pass = Located (RuleDecls pass) Source #

Located Rule Declarations

data RuleDecls pass Source #

Rule Declarations

Constructors

HsRules 

Fields

Instances
DataId pass => Data (RuleDecls pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: RuleDecls pass -> Constr Source #

dataTypeOf :: RuleDecls pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (RuleDecls pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: RuleDecls pass -> SDoc Source #

pprPrec :: Rational -> RuleDecls pass -> SDoc Source #

data RuleDecl pass Source #

Rule Declaration

Instances
DataId pass => Data (RuleDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: RuleDecl pass -> Constr Source #

dataTypeOf :: RuleDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (RuleDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: RuleDecl pass -> SDoc Source #

pprPrec :: Rational -> RuleDecl pass -> SDoc Source #

type LRuleDecl pass = Located (RuleDecl pass) Source #

Located Rule Declaration

data RuleBndr pass Source #

Rule Binder

Instances
DataId pass => Data (RuleBndr pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: RuleBndr pass -> Constr Source #

dataTypeOf :: RuleBndr pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (RuleBndr pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: RuleBndr pass -> SDoc Source #

pprPrec :: Rational -> RuleBndr pass -> SDoc Source #

type LRuleBndr pass = Located (RuleBndr pass) Source #

Located Rule Binder

VECTORISE declarations

data VectDecl pass Source #

Vectorise Declaration

Instances
DataId pass => Data (VectDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: VectDecl pass -> Constr Source #

dataTypeOf :: VectDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (VectDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: VectDecl pass -> SDoc Source #

pprPrec :: Rational -> VectDecl pass -> SDoc Source #

type LVectDecl pass = Located (VectDecl pass) Source #

Located Vectorise Declaration

default declarations

data DefaultDecl pass Source #

Default Declaration

Instances
DataId pass => Data (DefaultDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: DefaultDecl pass -> Constr Source #

dataTypeOf :: DefaultDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (DefaultDecl pass) # 
Instance details

Defined in HsDecls

type LDefaultDecl pass = Located (DefaultDecl pass) Source #

Located Default Declaration

Template haskell declaration splice

data SpliceExplicitFlag Source #

Constructors

ExplicitSplice

= $(f x y)

ImplicitSplice

= f x y, i.e. a naked top level expression

Instances
Data SpliceExplicitFlag # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: SpliceExplicitFlag -> Constr Source #

dataTypeOf :: SpliceExplicitFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

data SpliceDecl id Source #

Splice Declaration

Instances
DataId id => Data (SpliceDecl id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: SpliceDecl id -> Constr Source #

dataTypeOf :: SpliceDecl id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (SpliceDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: SpliceDecl pass -> SDoc Source #

pprPrec :: Rational -> SpliceDecl pass -> SDoc Source #

type LSpliceDecl pass = Located (SpliceDecl pass) Source #

Located Splice Declaration

Foreign function interface declarations

data ForeignDecl pass Source #

Foreign Declaration

Instances
DataId pass => Data (ForeignDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: ForeignDecl pass -> Constr Source #

dataTypeOf :: ForeignDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (ForeignDecl pass) # 
Instance details

Defined in HsDecls

type LForeignDecl pass = Located (ForeignDecl pass) Source #

Located Foreign Declaration

data ForeignImport Source #

Instances
Data ForeignImport # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: ForeignImport -> Constr Source #

dataTypeOf :: ForeignImport -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable ForeignImport # 
Instance details

Defined in HsDecls

data ForeignExport Source #

Instances
Data ForeignExport # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: ForeignExport -> Constr Source #

dataTypeOf :: ForeignExport -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable ForeignExport # 
Instance details

Defined in HsDecls

data CImportSpec Source #

Instances
Data CImportSpec # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: CImportSpec -> Constr Source #

dataTypeOf :: CImportSpec -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Data-constructor declarations

data ConDecl pass Source #

data T b = forall a. Eq a => MkT a b
  MkT :: forall b a. Eq a => MkT a b

data T b where
     MkT1 :: Int -> T Int

data T = Int MkT Int
       | MkT2

data T a where
     Int MkT Int :: T Int

data Constructor Declaration

Constructors

ConDeclGADT 

Fields

ConDeclH98 

Fields

Instances
DataId pass => Data (ConDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: ConDecl pass -> Constr Source #

dataTypeOf :: ConDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (ConDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: ConDecl pass -> SDoc Source #

pprPrec :: Rational -> ConDecl pass -> SDoc Source #

type LConDecl pass Source #

Arguments

 = Located (ConDecl pass)

May have AnnKeywordId : AnnSemi when in a GADT constructor list

Located data Constructor Declaration

type HsConDeclDetails pass = HsConDetails (LBangType pass) (Located [LConDeclField pass]) Source #

Haskell data Constructor Declaration Details

getConNames :: ConDecl pass -> [Located (IdP pass)] Source #

Document comments

data DocDecl Source #

Documentation comment Declaration

Instances
Data DocDecl # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: DocDecl -> Constr Source #

dataTypeOf :: DocDecl -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable DocDecl # 
Instance details

Defined in HsDecls

type LDocDecl = Located DocDecl Source #

Located Documentation comment Declaration

Deprecations

data WarnDecl pass Source #

Warning pragma Declaration

Constructors

Warning [Located (IdP pass)] WarningTxt 
Instances
DataId pass => Data (WarnDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: WarnDecl pass -> Constr Source #

dataTypeOf :: WarnDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

OutputableBndr (IdP pass) => Outputable (WarnDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: WarnDecl pass -> SDoc Source #

pprPrec :: Rational -> WarnDecl pass -> SDoc Source #

type LWarnDecl pass = Located (WarnDecl pass) Source #

Located Warning pragma Declaration

data WarnDecls pass Source #

Warning pragma Declarations

Constructors

Warnings 

Fields

Instances
DataId pass => Data (WarnDecls pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: WarnDecls pass -> Constr Source #

dataTypeOf :: WarnDecls pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

OutputableBndr (IdP pass) => Outputable (WarnDecls pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: WarnDecls pass -> SDoc Source #

pprPrec :: Rational -> WarnDecls pass -> SDoc Source #

type LWarnDecls pass = Located (WarnDecls pass) Source #

Located Warning Declarations

Annotations

data AnnDecl pass Source #

Annotation Declaration

Instances
DataId pass => Data (AnnDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: AnnDecl pass -> Constr Source #

dataTypeOf :: AnnDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (AnnDecl pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: AnnDecl pass -> SDoc Source #

pprPrec :: Rational -> AnnDecl pass -> SDoc Source #

type LAnnDecl pass = Located (AnnDecl pass) Source #

Located Annotation Declaration

data AnnProvenance name Source #

Annotation Provenance

Instances
Functor AnnProvenance # 
Instance details

Defined in HsDecls

Methods

fmap :: (a -> b) -> AnnProvenance a -> AnnProvenance b Source #

(<$) :: a -> AnnProvenance b -> AnnProvenance a Source #

Foldable AnnProvenance # 
Instance details

Defined in HsDecls

Methods

fold :: Monoid m => AnnProvenance m -> m Source #

foldMap :: Monoid m => (a -> m) -> AnnProvenance a -> m Source #

foldr :: (a -> b -> b) -> b -> AnnProvenance a -> b Source #

foldr' :: (a -> b -> b) -> b -> AnnProvenance a -> b Source #

foldl :: (b -> a -> b) -> b -> AnnProvenance a -> b Source #

foldl' :: (b -> a -> b) -> b -> AnnProvenance a -> b Source #

foldr1 :: (a -> a -> a) -> AnnProvenance a -> a Source #

foldl1 :: (a -> a -> a) -> AnnProvenance a -> a Source #

toList :: AnnProvenance a -> [a] Source #

null :: AnnProvenance a -> Bool Source #

length :: AnnProvenance a -> Int Source #

elem :: Eq a => a -> AnnProvenance a -> Bool Source #

maximum :: Ord a => AnnProvenance a -> a Source #

minimum :: Ord a => AnnProvenance a -> a Source #

sum :: Num a => AnnProvenance a -> a Source #

product :: Num a => AnnProvenance a -> a Source #

Traversable AnnProvenance # 
Instance details

Defined in HsDecls

Methods

traverse :: Applicative f => (a -> f b) -> AnnProvenance a -> f (AnnProvenance b) Source #

sequenceA :: Applicative f => AnnProvenance (f a) -> f (AnnProvenance a) Source #

mapM :: Monad m => (a -> m b) -> AnnProvenance a -> m (AnnProvenance b) Source #

sequence :: Monad m => AnnProvenance (m a) -> m (AnnProvenance a) Source #

Data pass => Data (AnnProvenance pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: AnnProvenance pass -> Constr Source #

dataTypeOf :: AnnProvenance pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Role annotations

data RoleAnnotDecl pass Source #

Role Annotation Declaration

Instances
DataId pass => Data (RoleAnnotDecl pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: RoleAnnotDecl pass -> Constr Source #

dataTypeOf :: RoleAnnotDecl pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

OutputableBndr (IdP pass) => Outputable (RoleAnnotDecl pass) # 
Instance details

Defined in HsDecls

type LRoleAnnotDecl pass = Located (RoleAnnotDecl pass) Source #

Located Role Annotation Declaration

Injective type families

data FamilyResultSig pass Source #

type Family Result Signature

Instances
DataId pass => Data (FamilyResultSig pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: FamilyResultSig pass -> Constr Source #

dataTypeOf :: FamilyResultSig pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

type LFamilyResultSig pass = Located (FamilyResultSig pass) Source #

Located type Family Result Signature

data InjectivityAnn pass Source #

If the user supplied an injectivity annotation it is represented using InjectivityAnn. At the moment this is a single injectivity condition - see Note [Injectivity annotation]. `Located name` stores the LHS of injectivity condition. `[Located name]` stores the RHS of injectivity condition. Example:

type family Foo a b c = r | r -> a c where ...

This will be represented as "InjectivityAnn r [a, c]"

Instances
DataId pass => Data (InjectivityAnn pass) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: InjectivityAnn pass -> Constr Source #

dataTypeOf :: InjectivityAnn pass -> DataType Source #

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

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

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

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

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

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

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

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

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

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

type LInjectivityAnn pass = Located (InjectivityAnn pass) Source #

Located Injectivity Annotation

resultVariableName :: FamilyResultSig a -> Maybe (IdP a) Source #

Maybe return name of the result type variable

Grouping

data HsGroup id Source #

Haskell Group

A HsDecl is categorised into a HsGroup before being fed to the renamer.

Instances
DataId id => Data (HsGroup id) # 
Instance details

Defined in HsDecls

Methods

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

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

toConstr :: HsGroup id -> Constr Source #

dataTypeOf :: HsGroup id -> DataType Source #

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

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

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

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

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

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

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

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

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

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

(SourceTextX pass, OutputableBndrId pass) => Outputable (HsGroup pass) # 
Instance details

Defined in HsDecls

Methods

ppr :: HsGroup pass -> SDoc Source #

pprPrec :: Rational -> HsGroup pass -> SDoc Source #