Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data HsScaled pass a = HsScaled (HsArrow pass) a
- hsMult :: HsScaled pass a -> HsArrow pass
- hsScaledThing :: HsScaled pass a -> a
- data HsArrow pass
- = HsUnrestrictedArrow !(XUnrestrictedArrow pass)
- | HsLinearArrow !(XLinearArrow pass)
- | HsExplicitMult !(XExplicitMult pass) !(LHsType pass)
- | XArrow !(XXArrow pass)
- type family XUnrestrictedArrow p
- type family XLinearArrow p
- type family XExplicitMult p
- type family XXArrow p
- data HsType pass
- = HsForAllTy {
- hst_xforall :: XForAllTy pass
- hst_tele :: HsForAllTelescope pass
- hst_body :: LHsType pass
- | HsQualTy { }
- | HsTyVar (XTyVar pass) PromotionFlag (LIdP pass)
- | HsAppTy (XAppTy pass) (LHsType pass) (LHsType pass)
- | HsAppKindTy (XAppKindTy pass) (LHsType pass) (LHsKind pass)
- | HsFunTy (XFunTy pass) (HsArrow pass) (LHsType pass) (LHsType pass)
- | HsListTy (XListTy pass) (LHsType pass)
- | HsTupleTy (XTupleTy pass) HsTupleSort [LHsType pass]
- | HsSumTy (XSumTy pass) [LHsType pass]
- | HsOpTy (XOpTy pass) PromotionFlag (LHsType pass) (LIdP pass) (LHsType pass)
- | HsParTy (XParTy pass) (LHsType pass)
- | HsIParamTy (XIParamTy pass) (XRec pass HsIPName) (LHsType pass)
- | HsStarTy (XStarTy pass) Bool
- | HsKindSig (XKindSig pass) (LHsType pass) (LHsKind pass)
- | HsSpliceTy (XSpliceTy pass) (HsUntypedSplice pass)
- | HsDocTy (XDocTy pass) (LHsType pass) (LHsDoc pass)
- | HsBangTy (XBangTy pass) HsSrcBang (LHsType pass)
- | HsRecTy (XRecTy pass) [LConDeclField pass]
- | HsExplicitListTy (XExplicitListTy pass) PromotionFlag [LHsType pass]
- | HsExplicitTupleTy (XExplicitTupleTy pass) [LHsType pass]
- | HsTyLit (XTyLit pass) (HsTyLit pass)
- | HsWildCardTy (XWildCardTy pass)
- | XHsType !(XXType pass)
- = HsForAllTy {
- type LHsType pass = XRec pass (HsType pass)
- type HsKind pass = HsType pass
- type LHsKind pass = XRec pass (HsKind pass)
- data HsBndrVis pass
- = HsBndrRequired !(XBndrRequired pass)
- | HsBndrInvisible !(XBndrInvisible pass)
- | XXBndrVis !(XXBndrVis pass)
- type family XBndrRequired p
- type family XBndrInvisible p
- type family XXBndrVis p
- isHsBndrInvisible :: HsBndrVis pass -> Bool
- data HsForAllTelescope pass
- = HsForAllVis {
- hsf_xvis :: XHsForAllVis pass
- hsf_vis_bndrs :: [LHsTyVarBndr () pass]
- | HsForAllInvis {
- hsf_xinvis :: XHsForAllInvis pass
- hsf_invis_bndrs :: [LHsTyVarBndr Specificity pass]
- | XHsForAllTelescope !(XXHsForAllTelescope pass)
- = HsForAllVis {
- data HsTyVarBndr flag pass
- = UserTyVar (XUserTyVar pass) flag (LIdP pass)
- | KindedTyVar (XKindedTyVar pass) flag (LIdP pass) (LHsKind pass)
- | XTyVarBndr !(XXTyVarBndr pass)
- type LHsTyVarBndr flag pass = XRec pass (HsTyVarBndr flag pass)
- data LHsQTyVars pass
- = HsQTvs {
- hsq_ext :: XHsQTvs pass
- hsq_explicit :: [LHsTyVarBndr (HsBndrVis pass) pass]
- | XLHsQTyVars !(XXLHsQTyVars pass)
- = HsQTvs {
- data HsOuterTyVarBndrs flag pass
- = HsOuterImplicit {
- hso_ximplicit :: XHsOuterImplicit pass
- | HsOuterExplicit {
- hso_xexplicit :: XHsOuterExplicit pass flag
- hso_bndrs :: [LHsTyVarBndr flag (NoGhcTc pass)]
- | XHsOuterTyVarBndrs !(XXHsOuterTyVarBndrs pass)
- = HsOuterImplicit {
- type HsOuterFamEqnTyVarBndrs = HsOuterTyVarBndrs ()
- type HsOuterSigTyVarBndrs = HsOuterTyVarBndrs Specificity
- data HsWildCardBndrs pass thing
- = HsWC { }
- | XHsWildCardBndrs !(XXHsWildCardBndrs pass thing)
- data HsPatSigType pass
- = HsPS { }
- | XHsPatSigType !(XXHsPatSigType pass)
- data HsSigType pass
- = HsSig { }
- | XHsSigType !(XXHsSigType pass)
- type LHsSigType pass = XRec pass (HsSigType pass)
- type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass)
- type LHsWcType pass = HsWildCardBndrs pass (LHsType pass)
- data HsTyPat pass
- type LHsTyPat pass = XRec pass (HsTyPat pass)
- data HsTupleSort
- type HsContext pass = [LHsType pass]
- type LHsContext pass = XRec pass (HsContext pass)
- data HsTyLit pass
- newtype HsIPName = HsIPName FastString
- hsIPNameFS :: HsIPName -> FastString
- data HsArg p tm ty
- type family XValArg p
- type family XTypeArg p
- type family XArgPar p
- type family XXArg p
- type LHsTypeArg p = HsArg p (LHsType p) (LHsKind p)
- type LBangType pass = XRec pass (BangType pass)
- type BangType pass = HsType pass
- data HsSrcBang = HsSrcBang SourceText SrcUnpackedness SrcStrictness
- data PromotionFlag
- isPromoted :: PromotionFlag -> Bool
- data ConDeclField pass
- = ConDeclField {
- cd_fld_ext :: XConDeclField pass
- cd_fld_names :: [LFieldOcc pass]
- cd_fld_type :: LBangType pass
- cd_fld_doc :: Maybe (LHsDoc pass)
- | XConDeclField !(XXConDeclField pass)
- = ConDeclField {
- type LConDeclField pass = XRec pass (ConDeclField pass)
- data HsConDetails tyarg arg rec
- noTypeArgs :: [Void]
- conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity
- data FieldOcc pass
- = FieldOcc {
- foExt :: XCFieldOcc pass
- foLabel :: XRec pass RdrName
- | XFieldOcc !(XXFieldOcc pass)
- = FieldOcc {
- type LFieldOcc pass = XRec pass (FieldOcc pass)
- data AmbiguousFieldOcc pass
- = Unambiguous (XUnambiguous pass) (XRec pass RdrName)
- | Ambiguous (XAmbiguous pass) (XRec pass RdrName)
- | XAmbiguousFieldOcc !(XXAmbiguousFieldOcc pass)
- type LAmbiguousFieldOcc pass = XRec pass (AmbiguousFieldOcc pass)
- mapHsOuterImplicit :: (XHsOuterImplicit pass -> XHsOuterImplicit pass) -> HsOuterTyVarBndrs flag pass -> HsOuterTyVarBndrs flag pass
- hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr (HsBndrVis pass) pass]
- isHsKindedTyVar :: HsTyVarBndr flag pass -> Bool
- hsPatSigType :: HsPatSigType pass -> LHsType pass
Documentation
This is used in the syntax. In constructor declaration. It must keep the arrow representation.
Instances
Data thing => Data (HsScaled GhcPs thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcPs thing -> c (HsScaled GhcPs thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcPs thing) # toConstr :: HsScaled GhcPs thing -> Constr # dataTypeOf :: HsScaled GhcPs thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcPs thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcPs thing)) # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcPs thing -> HsScaled GhcPs thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcPs thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcPs thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcPs thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcPs thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcPs thing -> m (HsScaled GhcPs thing) # | |
Data thing => Data (HsScaled GhcRn thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcRn thing -> c (HsScaled GhcRn thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcRn thing) # toConstr :: HsScaled GhcRn thing -> Constr # dataTypeOf :: HsScaled GhcRn thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcRn thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcRn thing)) # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcRn thing -> HsScaled GhcRn thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcRn thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcRn thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcRn thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcRn thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcRn thing -> m (HsScaled GhcRn thing) # | |
Data thing => Data (HsScaled GhcTc thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsScaled GhcTc thing -> c (HsScaled GhcTc thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsScaled GhcTc thing) # toConstr :: HsScaled GhcTc thing -> Constr # dataTypeOf :: HsScaled GhcTc thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsScaled GhcTc thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsScaled GhcTc thing)) # gmapT :: (forall b. Data b => b -> b) -> HsScaled GhcTc thing -> HsScaled GhcTc thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcTc thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsScaled GhcTc thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsScaled GhcTc thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsScaled GhcTc thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsScaled GhcTc thing -> m (HsScaled GhcTc thing) # |
hsScaledThing :: HsScaled pass a -> a Source #
Denotes the type of arrows in the surface language
HsUnrestrictedArrow !(XUnrestrictedArrow pass) | a -> b or a → b |
HsLinearArrow !(XLinearArrow pass) | a %1 -> b or a %1 → b, or a ⊸ b |
HsExplicitMult !(XExplicitMult pass) !(LHsType pass) | a %m -> b or a %m → b (very much including `a %Many -> b`!
This is how the programmer wrote it). It is stored as an
|
XArrow !(XXArrow pass) |
Instances
OutputableBndrId pass => Outputable (HsArrow (GhcPass pass)) Source # | |
Data (HsArrow GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcPs -> c (HsArrow GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcPs) # toConstr :: HsArrow GhcPs -> Constr # dataTypeOf :: HsArrow GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcPs -> HsArrow GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcPs -> m (HsArrow GhcPs) # | |
Data (HsArrow GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcRn -> c (HsArrow GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcRn) # toConstr :: HsArrow GhcRn -> Constr # dataTypeOf :: HsArrow GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcRn -> HsArrow GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcRn -> m (HsArrow GhcRn) # | |
Data (HsArrow GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsArrow GhcTc -> c (HsArrow GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArrow GhcTc) # toConstr :: HsArrow GhcTc -> Constr # dataTypeOf :: HsArrow GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArrow GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArrow GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsArrow GhcTc -> HsArrow GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArrow GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArrow GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArrow GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArrow GhcTc -> m (HsArrow GhcTc) # |
type family XUnrestrictedArrow p Source #
Instances
type XUnrestrictedArrow GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XUnrestrictedArrow GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XUnrestrictedArrow GhcTc Source # | |
Defined in GHC.Hs.Type |
type family XLinearArrow p Source #
Instances
type XLinearArrow GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XLinearArrow GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XLinearArrow GhcTc Source # | |
Defined in GHC.Hs.Type |
type family XExplicitMult p Source #
Instances
type XExplicitMult GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XExplicitMult GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XExplicitMult GhcTc Source # | |
Defined in GHC.Hs.Type |
Haskell Type
Instances
DisambTD (HsType GhcPs) Source # | |
Defined in GHC.Parser.PostProcess mkHsAppTyHeadPV :: LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkHsAppTyPV :: LocatedA (HsType GhcPs) -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkHsAppKindTyPV :: LocatedA (HsType GhcPs) -> EpToken "@" -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkHsOpTyPV :: PromotionFlag -> LHsType GhcPs -> LocatedN RdrName -> LHsType GhcPs -> PV (LocatedA (HsType GhcPs)) Source # mkUnpackednessPV :: Located UnpackednessPragma -> LocatedA (HsType GhcPs) -> PV (LocatedA (HsType GhcPs)) Source # | |
OutputableBndrId p => Outputable (HsType (GhcPass p)) Source # | |
Data (HsType GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcPs -> c (HsType GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcPs) # toConstr :: HsType GhcPs -> Constr # dataTypeOf :: HsType GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsType GhcPs -> HsType GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcPs -> m (HsType GhcPs) # | |
Data (HsType GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcRn -> c (HsType GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcRn) # toConstr :: HsType GhcRn -> Constr # dataTypeOf :: HsType GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsType GhcRn -> HsType GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcRn -> m (HsType GhcRn) # | |
Data (HsType GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType GhcTc -> c (HsType GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType GhcTc) # toConstr :: HsType GhcTc -> Constr # dataTypeOf :: HsType GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsType GhcTc -> HsType GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsType GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType GhcTc -> m (HsType GhcTc) # | |
type Anno (BangType (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsKind (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsType (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno [LocatedA (HsType (GhcPass p))] Source # | |
Defined in GHC.Hs.Type | |
type Anno (FamEqn p (LocatedA (HsType p))) Source # | |
Defined in GHC.Hs.Decls |
= XRec pass (HsType pass) | May have |
Located Haskell Type
HsBndrRequired !(XBndrRequired pass) | |
HsBndrInvisible !(XBndrInvisible pass) | |
XXBndrVis !(XXBndrVis pass) |
Instances
Data (HsBndrVis GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBndrVis GhcPs -> c (HsBndrVis GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBndrVis GhcPs) # toConstr :: HsBndrVis GhcPs -> Constr # dataTypeOf :: HsBndrVis GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBndrVis GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBndrVis GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsBndrVis GhcPs -> HsBndrVis GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBndrVis GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBndrVis GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBndrVis GhcPs -> m (HsBndrVis GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcPs -> m (HsBndrVis GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcPs -> m (HsBndrVis GhcPs) # | |
Data (HsBndrVis GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBndrVis GhcRn -> c (HsBndrVis GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBndrVis GhcRn) # toConstr :: HsBndrVis GhcRn -> Constr # dataTypeOf :: HsBndrVis GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBndrVis GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBndrVis GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsBndrVis GhcRn -> HsBndrVis GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBndrVis GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBndrVis GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBndrVis GhcRn -> m (HsBndrVis GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcRn -> m (HsBndrVis GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcRn -> m (HsBndrVis GhcRn) # | |
Data (HsBndrVis GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsBndrVis GhcTc -> c (HsBndrVis GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsBndrVis GhcTc) # toConstr :: HsBndrVis GhcTc -> Constr # dataTypeOf :: HsBndrVis GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsBndrVis GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsBndrVis GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsBndrVis GhcTc -> HsBndrVis GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsBndrVis GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsBndrVis GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsBndrVis GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsBndrVis GhcTc -> m (HsBndrVis GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcTc -> m (HsBndrVis GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsBndrVis GhcTc -> m (HsBndrVis GhcTc) # | |
OutputableBndrFlag (HsBndrVis (GhcPass p')) p Source # | |
Defined in GHC.Hs.Type pprTyVarBndr :: HsTyVarBndr (HsBndrVis (GhcPass p')) (GhcPass p) -> SDoc |
type family XBndrRequired p Source #
Instances
type XBndrRequired (GhcPass _1) Source # | |
Defined in GHC.Hs.Type |
type family XBndrInvisible p Source #
Instances
type XBndrInvisible GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XBndrInvisible GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XBndrInvisible GhcTc Source # | |
Defined in GHC.Hs.Type |
type family XXBndrVis p Source #
Instances
type XXBndrVis (GhcPass _1) Source # | |
Defined in GHC.Hs.Type |
isHsBndrInvisible :: HsBndrVis pass -> Bool Source #
data HsForAllTelescope pass Source #
The type variable binders in an HsForAllTy
.
See also Note [Variable Specificity and Forall Visibility]
in
GHC.Tc.Gen.HsType.
HsForAllVis | A visible |
| |
HsForAllInvis | An invisible |
| |
XHsForAllTelescope !(XXHsForAllTelescope pass) |
Instances
OutputableBndrId p => Outputable (HsForAllTelescope (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
Data (HsForAllTelescope GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcPs -> c (HsForAllTelescope GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcPs) # toConstr :: HsForAllTelescope GhcPs -> Constr # dataTypeOf :: HsForAllTelescope GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcPs -> HsForAllTelescope GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcPs -> m (HsForAllTelescope GhcPs) # | |
Data (HsForAllTelescope GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcRn -> c (HsForAllTelescope GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcRn) # toConstr :: HsForAllTelescope GhcRn -> Constr # dataTypeOf :: HsForAllTelescope GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcRn -> HsForAllTelescope GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcRn -> m (HsForAllTelescope GhcRn) # | |
Data (HsForAllTelescope GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsForAllTelescope GhcTc -> c (HsForAllTelescope GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsForAllTelescope GhcTc) # toConstr :: HsForAllTelescope GhcTc -> Constr # dataTypeOf :: HsForAllTelescope GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsForAllTelescope GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsForAllTelescope GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsForAllTelescope GhcTc -> HsForAllTelescope GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsForAllTelescope GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsForAllTelescope GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsForAllTelescope GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsForAllTelescope GhcTc -> m (HsForAllTelescope GhcTc) # |
data HsTyVarBndr flag pass Source #
Haskell Type Variable Binder
The flag annotates the binder. It is Specificity
in places where
explicit specificity is allowed (e.g. x :: forall {a} b. ...) or
()
in other places.
UserTyVar (XUserTyVar pass) flag (LIdP pass) | |
KindedTyVar (XKindedTyVar pass) flag (LIdP pass) (LHsKind pass) | |
XTyVarBndr !(XXTyVarBndr pass) |
Instances
NamedThing (HsTyVarBndr flag GhcRn) Source # | |
Defined in GHC.Hs.Type getOccName :: HsTyVarBndr flag GhcRn -> OccName Source # | |
(OutputableBndrId p, OutputableBndrFlag flag p) => Outputable (HsTyVarBndr flag (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
Data flag => Data (HsTyVarBndr flag GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcPs -> c (HsTyVarBndr flag GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcPs) # toConstr :: HsTyVarBndr flag GhcPs -> Constr # dataTypeOf :: HsTyVarBndr flag GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcPs -> HsTyVarBndr flag GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcPs -> m (HsTyVarBndr flag GhcPs) # | |
Data flag => Data (HsTyVarBndr flag GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcRn -> c (HsTyVarBndr flag GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcRn) # toConstr :: HsTyVarBndr flag GhcRn -> Constr # dataTypeOf :: HsTyVarBndr flag GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcRn -> HsTyVarBndr flag GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcRn -> m (HsTyVarBndr flag GhcRn) # | |
Data flag => Data (HsTyVarBndr flag GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr flag GhcTc -> c (HsTyVarBndr flag GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr flag GhcTc) # toConstr :: HsTyVarBndr flag GhcTc -> Constr # dataTypeOf :: HsTyVarBndr flag GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr flag GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr flag GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr flag GhcTc -> HsTyVarBndr flag GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr flag GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr flag GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr flag GhcTc -> m (HsTyVarBndr flag GhcTc) # | |
type Anno (HsTyVarBndr _flag (GhcPass _1)) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag GhcPs) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag GhcRn) Source # | |
Defined in GHC.Hs.Type | |
type Anno (HsTyVarBndr _flag GhcTc) Source # | |
Defined in GHC.Hs.Type |
type LHsTyVarBndr flag pass = XRec pass (HsTyVarBndr flag pass) Source #
Located Haskell Type Variable Binder
data LHsQTyVars pass Source #
Located Haskell Quantified Type Variables
HsQTvs | |
| |
XLHsQTyVars !(XXLHsQTyVars pass) |
Instances
OutputableBndrId p => Outputable (LHsQTyVars (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
Data (LHsQTyVars GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcPs -> c (LHsQTyVars GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcPs) # toConstr :: LHsQTyVars GhcPs -> Constr # dataTypeOf :: LHsQTyVars GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcPs -> LHsQTyVars GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcPs -> m (LHsQTyVars GhcPs) # | |
Data (LHsQTyVars GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcRn -> c (LHsQTyVars GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcRn) # toConstr :: LHsQTyVars GhcRn -> Constr # dataTypeOf :: LHsQTyVars GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcRn -> LHsQTyVars GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcRn -> m (LHsQTyVars GhcRn) # | |
Data (LHsQTyVars GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars GhcTc -> c (LHsQTyVars GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars GhcTc) # toConstr :: LHsQTyVars GhcTc -> Constr # dataTypeOf :: LHsQTyVars GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars GhcTc -> LHsQTyVars GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars GhcTc -> m (LHsQTyVars GhcTc) # |
data HsOuterTyVarBndrs flag pass Source #
The outermost type variables in a type that obeys the forall
-or-nothing
rule. See Note [forall-or-nothing rule]
.
HsOuterImplicit | Implicit forall, e.g.,
|
| |
HsOuterExplicit | Explicit forall, e.g.,
|
| |
XHsOuterTyVarBndrs !(XXHsOuterTyVarBndrs pass) |
Instances
(OutputableBndrFlag flag p, OutputableBndrFlag flag (NoGhcTcPass p), OutputableBndrId p) => Outputable (HsOuterTyVarBndrs flag (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
Data flag => Data (HsOuterTyVarBndrs flag GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcPs -> c (HsOuterTyVarBndrs flag GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcPs) # toConstr :: HsOuterTyVarBndrs flag GhcPs -> Constr # dataTypeOf :: HsOuterTyVarBndrs flag GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcPs -> HsOuterTyVarBndrs flag GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcPs -> m (HsOuterTyVarBndrs flag GhcPs) # | |
Data flag => Data (HsOuterTyVarBndrs flag GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcRn -> c (HsOuterTyVarBndrs flag GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcRn) # toConstr :: HsOuterTyVarBndrs flag GhcRn -> Constr # dataTypeOf :: HsOuterTyVarBndrs flag GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcRn -> HsOuterTyVarBndrs flag GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcRn -> m (HsOuterTyVarBndrs flag GhcRn) # | |
Data flag => Data (HsOuterTyVarBndrs flag GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsOuterTyVarBndrs flag GhcTc -> c (HsOuterTyVarBndrs flag GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsOuterTyVarBndrs flag GhcTc) # toConstr :: HsOuterTyVarBndrs flag GhcTc -> Constr # dataTypeOf :: HsOuterTyVarBndrs flag GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsOuterTyVarBndrs flag GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsOuterTyVarBndrs flag GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsOuterTyVarBndrs flag GhcTc -> HsOuterTyVarBndrs flag GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsOuterTyVarBndrs flag GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsOuterTyVarBndrs flag GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsOuterTyVarBndrs flag GhcTc -> m (HsOuterTyVarBndrs flag GhcTc) # | |
type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) Source # | |
Defined in GHC.Hs.Type |
type HsOuterFamEqnTyVarBndrs = HsOuterTyVarBndrs () Source #
Used for type-family instance equations, e.g.,
type instance forall a. F [a] = Tree a
The notion of specificity is irrelevant in type family equations, so we use
()
for the HsOuterTyVarBndrs
flag
.
type HsOuterSigTyVarBndrs = HsOuterTyVarBndrs Specificity Source #
Used for signatures, e.g.,
f :: forall a {b}. blah
We use Specificity
for the HsOuterTyVarBndrs
flag
to allow
distinguishing between specified and inferred type variables.
data HsWildCardBndrs pass thing Source #
Haskell Wildcard Binders
HsWC | |
XHsWildCardBndrs !(XXHsWildCardBndrs pass thing) |
Instances
Outputable thing => Outputable (HsWildCardBndrs (GhcPass p) thing) Source # | |
Defined in GHC.Hs.Type | |
Data thing => Data (HsWildCardBndrs GhcPs thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcPs thing -> c (HsWildCardBndrs GhcPs thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcPs thing) # toConstr :: HsWildCardBndrs GhcPs thing -> Constr # dataTypeOf :: HsWildCardBndrs GhcPs thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcPs thing)) # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcPs thing -> HsWildCardBndrs GhcPs thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcPs thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcPs thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcPs thing -> m (HsWildCardBndrs GhcPs thing) # | |
Data thing => Data (HsWildCardBndrs GhcRn thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcRn thing -> c (HsWildCardBndrs GhcRn thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcRn thing) # toConstr :: HsWildCardBndrs GhcRn thing -> Constr # dataTypeOf :: HsWildCardBndrs GhcRn thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcRn thing)) # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcRn thing -> HsWildCardBndrs GhcRn thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcRn thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcRn thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcRn thing -> m (HsWildCardBndrs GhcRn thing) # | |
Data thing => Data (HsWildCardBndrs GhcTc thing) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs GhcTc thing -> c (HsWildCardBndrs GhcTc thing) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs GhcTc thing) # toConstr :: HsWildCardBndrs GhcTc thing -> Constr # dataTypeOf :: HsWildCardBndrs GhcTc thing -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs GhcTc thing)) # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs GhcTc thing -> HsWildCardBndrs GhcTc thing # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs GhcTc thing -> r # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs GhcTc thing -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs GhcTc thing -> m (HsWildCardBndrs GhcTc thing) # |
data HsPatSigType pass Source #
Types that can appear in pattern signatures, as well as the signatures for
term-level binders in RULES.
See Note [Pattern signature binders and scoping]
.
This is very similar to HsSigWcType
, but with
slightly different semantics: see Note [HsType binders]
.
See also Note [The wildcard story for types]
.
HsPS | |
XHsPatSigType !(XXHsPatSigType pass) |
Instances
OutputableBndrId p => Outputable (HsPatSigType (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
Data (HsPatSigType GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcPs -> c (HsPatSigType GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcPs) # toConstr :: HsPatSigType GhcPs -> Constr # dataTypeOf :: HsPatSigType GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcPs -> HsPatSigType GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcPs -> m (HsPatSigType GhcPs) # | |
Data (HsPatSigType GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcRn -> c (HsPatSigType GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcRn) # toConstr :: HsPatSigType GhcRn -> Constr # dataTypeOf :: HsPatSigType GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcRn -> HsPatSigType GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcRn -> m (HsPatSigType GhcRn) # | |
Data (HsPatSigType GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsPatSigType GhcTc -> c (HsPatSigType GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatSigType GhcTc) # toConstr :: HsPatSigType GhcTc -> Constr # dataTypeOf :: HsPatSigType GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatSigType GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatSigType GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsPatSigType GhcTc -> HsPatSigType GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatSigType GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsPatSigType GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatSigType GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatSigType GhcTc -> m (HsPatSigType GhcTc) # |
A type signature that obeys the forall
-or-nothing rule. In other
words, an LHsType
that uses an HsOuterSigTyVarBndrs
to represent its
outermost type variable quantification.
See Note [Representing type signatures]
.
HsSig | |
XHsSigType !(XXHsSigType pass) |
Instances
OutputableBndrId p => Outputable (HsSigType (GhcPass p)) Source # | |
Data (HsSigType GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcPs -> c (HsSigType GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcPs) # toConstr :: HsSigType GhcPs -> Constr # dataTypeOf :: HsSigType GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcPs -> HsSigType GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcPs -> m (HsSigType GhcPs) # | |
Data (HsSigType GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcRn -> c (HsSigType GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcRn) # toConstr :: HsSigType GhcRn -> Constr # dataTypeOf :: HsSigType GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcRn -> HsSigType GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcRn -> m (HsSigType GhcRn) # | |
Data (HsSigType GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSigType GhcTc -> c (HsSigType GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsSigType GhcTc) # toConstr :: HsSigType GhcTc -> Constr # dataTypeOf :: HsSigType GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsSigType GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsSigType GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsSigType GhcTc -> HsSigType GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSigType GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSigType GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSigType GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSigType GhcTc -> m (HsSigType GhcTc) # | |
type Anno (HsSigType (GhcPass p)) Source # | |
Defined in GHC.Hs.Type |
type LHsSigType pass = XRec pass (HsSigType pass) Source #
Located Haskell Signature Type
type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass) Source #
Located Haskell Signature Wildcard Type
type LHsWcType pass = HsWildCardBndrs pass (LHsType pass) Source #
Located Haskell Wildcard Type
Instances
OutputableBndrId p => Outputable (HsTyPat (GhcPass p)) Source # | |
Data (HsTyPat GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyPat GhcPs -> c (HsTyPat GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyPat GhcPs) # toConstr :: HsTyPat GhcPs -> Constr # dataTypeOf :: HsTyPat GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyPat GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyPat GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsTyPat GhcPs -> HsTyPat GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyPat GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyPat GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyPat GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyPat GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyPat GhcPs -> m (HsTyPat GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyPat GhcPs -> m (HsTyPat GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyPat GhcPs -> m (HsTyPat GhcPs) # | |
Data (HsTyPat GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyPat GhcRn -> c (HsTyPat GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyPat GhcRn) # toConstr :: HsTyPat GhcRn -> Constr # dataTypeOf :: HsTyPat GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyPat GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyPat GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsTyPat GhcRn -> HsTyPat GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyPat GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyPat GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyPat GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyPat GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyPat GhcRn -> m (HsTyPat GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyPat GhcRn -> m (HsTyPat GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyPat GhcRn -> m (HsTyPat GhcRn) # | |
Data (HsTyPat GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyPat GhcTc -> c (HsTyPat GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyPat GhcTc) # toConstr :: HsTyPat GhcTc -> Constr # dataTypeOf :: HsTyPat GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyPat GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyPat GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsTyPat GhcTc -> HsTyPat GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyPat GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyPat GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyPat GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyPat GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyPat GhcTc -> m (HsTyPat GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyPat GhcTc -> m (HsTyPat GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyPat GhcTc -> m (HsTyPat GhcTc) # |
data HsTupleSort Source #
Haskell Tuple Sort
Instances
Data HsTupleSort Source # | |
Defined in Language.Haskell.Syntax.Type gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTupleSort # toConstr :: HsTupleSort -> Constr # dataTypeOf :: HsTupleSort -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTupleSort) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTupleSort) # gmapT :: (forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTupleSort -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort # |
type LHsContext pass Source #
= XRec pass (HsContext pass) |
|
Located Haskell Context
Haskell Type Literal
HsNumTy (XNumTy pass) Integer | |
HsStrTy (XStrTy pass) FastString | |
HsCharTy (XCharTy pass) Char | |
XTyLit !(XXTyLit pass) |
Instances
OutputableBndrId p => Outputable (HsTyLit (GhcPass p)) Source # | |
Data (HsTyLit GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit GhcPs -> c (HsTyLit GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyLit GhcPs) # toConstr :: HsTyLit GhcPs -> Constr # dataTypeOf :: HsTyLit GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyLit GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyLit GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> HsTyLit GhcPs -> HsTyLit GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit GhcPs -> m (HsTyLit GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcPs -> m (HsTyLit GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcPs -> m (HsTyLit GhcPs) # | |
Data (HsTyLit GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit GhcRn -> c (HsTyLit GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyLit GhcRn) # toConstr :: HsTyLit GhcRn -> Constr # dataTypeOf :: HsTyLit GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyLit GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyLit GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> HsTyLit GhcRn -> HsTyLit GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit GhcRn -> m (HsTyLit GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcRn -> m (HsTyLit GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcRn -> m (HsTyLit GhcRn) # | |
Data (HsTyLit GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit GhcTc -> c (HsTyLit GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyLit GhcTc) # toConstr :: HsTyLit GhcTc -> Constr # dataTypeOf :: HsTyLit GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyLit GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyLit GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> HsTyLit GhcTc -> HsTyLit GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit GhcTc -> m (HsTyLit GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcTc -> m (HsTyLit GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit GhcTc -> m (HsTyLit GhcTc) # |
These names are used early on to store the names of implicit parameters. They completely disappear after type-checking.
Instances
Outputable HsIPName Source # | |
OutputableBndr HsIPName Source # | |
Defined in GHC.Hs.Type | |
Data HsIPName Source # | |
Defined in Language.Haskell.Syntax.Type gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPName -> c HsIPName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsIPName # toConstr :: HsIPName -> Constr # dataTypeOf :: HsIPName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsIPName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName) # gmapT :: (forall b. Data b => b -> b) -> HsIPName -> HsIPName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r # gmapQ :: (forall d. Data d => d -> u) -> HsIPName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName # | |
Eq HsIPName Source # | |
type Anno HsIPName Source # | |
Defined in GHC.Hs.Type |
hsIPNameFS :: HsIPName -> FastString Source #
Arguments in an expression/type after splitting
Instances
(HasLoc tm, HasLoc ty) => HasLoc (HsArg (GhcPass p) tm ty) Source # | |
(Outputable tm, Outputable ty) => Outputable (HsArg (GhcPass p) tm ty) Source # | This instance is meant for debug-printing purposes. If you wish to
pretty-print an application of |
(Data a, Data b) => Data (HsArg GhcPs a b) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsArg GhcPs a b -> c (HsArg GhcPs a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg GhcPs a b) # toConstr :: HsArg GhcPs a b -> Constr # dataTypeOf :: HsArg GhcPs a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg GhcPs a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg GhcPs a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsArg GhcPs a b -> HsArg GhcPs a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcPs a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcPs a b -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg GhcPs a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg GhcPs a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg GhcPs a b -> m (HsArg GhcPs a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcPs a b -> m (HsArg GhcPs a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcPs a b -> m (HsArg GhcPs a b) # | |
(Data a, Data b) => Data (HsArg GhcRn a b) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsArg GhcRn a b -> c (HsArg GhcRn a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg GhcRn a b) # toConstr :: HsArg GhcRn a b -> Constr # dataTypeOf :: HsArg GhcRn a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg GhcRn a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg GhcRn a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsArg GhcRn a b -> HsArg GhcRn a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcRn a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcRn a b -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg GhcRn a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg GhcRn a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg GhcRn a b -> m (HsArg GhcRn a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcRn a b -> m (HsArg GhcRn a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcRn a b -> m (HsArg GhcRn a b) # | |
(Data a, Data b) => Data (HsArg GhcTc a b) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsArg GhcTc a b -> c (HsArg GhcTc a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsArg GhcTc a b) # toConstr :: HsArg GhcTc a b -> Constr # dataTypeOf :: HsArg GhcTc a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsArg GhcTc a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsArg GhcTc a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsArg GhcTc a b -> HsArg GhcTc a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcTc a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsArg GhcTc a b -> r # gmapQ :: (forall d. Data d => d -> u) -> HsArg GhcTc a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsArg GhcTc a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsArg GhcTc a b -> m (HsArg GhcTc a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcTc a b -> m (HsArg GhcTc a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsArg GhcTc a b -> m (HsArg GhcTc a b) # |
type family XTypeArg p Source #
Instances
type XTypeArg GhcPs Source # | |
Defined in GHC.Hs.Type | |
type XTypeArg GhcRn Source # | |
Defined in GHC.Hs.Type | |
type XTypeArg GhcTc Source # | |
Defined in GHC.Hs.Type |
Instances
type XXArg (GhcPass _1) Source # | |
Defined in GHC.Hs.Type |
Haskell Source Bang
Bangs on data constructor arguments as the user wrote them in the source code.
(HsSrcBang _ SrcUnpack SrcLazy)
and
(HsSrcBang _ SrcUnpack NoSrcStrict)
(without StrictData) makes no sense, we
emit a warning (in checkValidDataCon) and treat it like
(HsSrcBang _ NoSrcUnpack SrcLazy)
Instances
Outputable HsSrcBang Source # | |
Data HsSrcBang Source # | |
Defined in GHC.Core.DataCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsSrcBang # toConstr :: HsSrcBang -> Constr # dataTypeOf :: HsSrcBang -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsSrcBang) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang) # gmapT :: (forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r # gmapQ :: (forall d. Data d => d -> u) -> HsSrcBang -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSrcBang -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang # |
data PromotionFlag Source #
Is a TyCon a promoted data constructor or just a normal type constructor?
Instances
isPromoted :: PromotionFlag -> Bool Source #
data ConDeclField pass Source #
Constructor Declaration Field
ConDeclField | |
| |
XConDeclField !(XXConDeclField pass) |
Instances
OutputableBndrId p => Outputable (ConDeclField (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
Data (ConDeclField GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcPs -> c (ConDeclField GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcPs) # toConstr :: ConDeclField GhcPs -> Constr # dataTypeOf :: ConDeclField GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcPs -> ConDeclField GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcPs -> m (ConDeclField GhcPs) # | |
Data (ConDeclField GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcRn -> c (ConDeclField GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcRn) # toConstr :: ConDeclField GhcRn -> Constr # dataTypeOf :: ConDeclField GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcRn -> ConDeclField GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcRn -> m (ConDeclField GhcRn) # | |
Data (ConDeclField GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField GhcTc -> c (ConDeclField GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField GhcTc) # toConstr :: ConDeclField GhcTc -> Constr # dataTypeOf :: ConDeclField GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> ConDeclField GhcTc -> ConDeclField GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField GhcTc -> m (ConDeclField GhcTc) # | |
type Anno (ConDeclField (GhcPass p)) Source # | |
Defined in GHC.Hs.Type | |
type Anno [LocatedA (ConDeclField (GhcPass _1))] Source # | |
Defined in GHC.Hs.Decls |
type LConDeclField pass Source #
= XRec pass (ConDeclField pass) | May have |
Located Constructor Declaration Field
data HsConDetails tyarg arg rec Source #
Describes the arguments to a data constructor. This is a common representation for several constructor-related concepts, including:
- The arguments in a Haskell98-style constructor declaration
(see
HsConDeclH98Details
in GHC.Hs.Decls). - The arguments in constructor patterns in
case
/function definitions (seeHsConPatDetails
in GHC.Hs.Pat). - The left-hand side arguments in a pattern synonym binding
(see
HsPatSynDetails
in GHC.Hs.Binds).
One notable exception is the arguments in a GADT constructor, which uses
a separate data type entirely (see HsConDeclGADTDetails
in
GHC.Hs.Decls). This is because GADT constructors cannot be declared with
infix syntax, unlike the concepts above (#18844).
Instances
(Outputable tyarg, Outputable arg, Outputable rec) => Outputable (HsConDetails tyarg arg rec) Source # | |
Defined in GHC.Hs.Type ppr :: HsConDetails tyarg arg rec -> SDoc Source # | |
(Data tyarg, Data rec, Data arg) => Data (HsConDetails tyarg arg rec) Source # | |
Defined in Language.Haskell.Syntax.Type gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDetails tyarg arg rec -> c (HsConDetails tyarg arg rec) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDetails tyarg arg rec) # toConstr :: HsConDetails tyarg arg rec -> Constr # dataTypeOf :: HsConDetails tyarg arg rec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDetails tyarg arg rec)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDetails tyarg arg rec)) # gmapT :: (forall b. Data b => b -> b) -> HsConDetails tyarg arg rec -> HsConDetails tyarg arg rec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails tyarg arg rec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails tyarg arg rec -> r # gmapQ :: (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDetails tyarg arg rec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails tyarg arg rec -> m (HsConDetails tyarg arg rec) # |
noTypeArgs :: [Void] Source #
An empty list that can be used to indicate that there are no type arguments allowed in cases where HsConDetails is applied to Void.
conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity Source #
Field Occurrence
Represents an *occurrence* of a field. This may or may not be a
binding occurrence (e.g. this type is used in ConDeclField
and
RecordPatSynField
which bind their fields, but also in
HsRecField
for record construction and patterns, which do not).
We store both the RdrName
the user originally wrote, and after
the renamer we use the extension field to store the selector
function.
FieldOcc | |
| |
XFieldOcc !(XXFieldOcc pass) |
Instances
Outputable (XRec pass RdrName) => Outputable (FieldOcc pass) Source # | |
(UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (FieldOcc pass) Source # | |
Defined in GHC.Hs.Type pprBndr :: BindingSite -> FieldOcc pass -> SDoc Source # pprPrefixOcc :: FieldOcc pass -> SDoc Source # pprInfixOcc :: FieldOcc pass -> SDoc Source # bndrIsJoin_maybe :: FieldOcc pass -> JoinPointHood Source # | |
Data (FieldOcc GhcPs) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcPs -> c (FieldOcc GhcPs) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcPs) # toConstr :: FieldOcc GhcPs -> Constr # dataTypeOf :: FieldOcc GhcPs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcPs)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcPs)) # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcPs -> FieldOcc GhcPs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcPs -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcPs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcPs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcPs -> m (FieldOcc GhcPs) # | |
Data (FieldOcc GhcRn) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcRn -> c (FieldOcc GhcRn) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcRn) # toConstr :: FieldOcc GhcRn -> Constr # dataTypeOf :: FieldOcc GhcRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcRn)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcRn)) # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcRn -> FieldOcc GhcRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcRn -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcRn -> m (FieldOcc GhcRn) # | |
Data (FieldOcc GhcTc) Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc GhcTc -> c (FieldOcc GhcTc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc GhcTc) # toConstr :: FieldOcc GhcTc -> Constr # dataTypeOf :: FieldOcc GhcTc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc GhcTc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc GhcTc)) # gmapT :: (forall b. Data b => b -> b) -> FieldOcc GhcTc -> FieldOcc GhcTc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc GhcTc -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc GhcTc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc GhcTc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc GhcTc -> m (FieldOcc GhcTc) # | |
(Eq (XRec pass RdrName), Eq (XCFieldOcc pass), Eq (XXFieldOcc pass)) => Eq (FieldOcc pass) Source # | |
(UnXRec pass, OutputableBndr (XRec pass RdrName)) => OutputableBndr (GenLocated SrcSpan (FieldOcc pass)) Source # | |
Defined in GHC.Hs.Type pprBndr :: BindingSite -> GenLocated SrcSpan (FieldOcc pass) -> SDoc Source # pprPrefixOcc :: GenLocated SrcSpan (FieldOcc pass) -> SDoc Source # pprInfixOcc :: GenLocated SrcSpan (FieldOcc pass) -> SDoc Source # bndrIsJoin_maybe :: GenLocated SrcSpan (FieldOcc pass) -> JoinPointHood Source # | |
type Anno (FieldOcc (GhcPass p)) Source # | |
Defined in GHC.Hs.Type |
data AmbiguousFieldOcc pass Source #
Ambiguous Field Occurrence
Represents an *occurrence* of a field that is potentially
ambiguous after the renamer, with the ambiguity resolved by the
typechecker. We always store the RdrName
that the user
originally wrote, and store the selector function after the renamer
(for unambiguous occurrences) or the typechecker (for ambiguous
occurrences).
See Note [HsRecField and HsRecUpdField] in GHC.Hs.Pat. See Note [Located RdrNames] in GHC.Hs.Expr.
Unambiguous (XUnambiguous pass) (XRec pass RdrName) | |
Ambiguous (XAmbiguous pass) (XRec pass RdrName) | |
XAmbiguousFieldOcc !(XXAmbiguousFieldOcc pass) |
Instances
type LAmbiguousFieldOcc pass = XRec pass (AmbiguousFieldOcc pass) Source #
Located Ambiguous Field Occurrence
mapHsOuterImplicit :: (XHsOuterImplicit pass -> XHsOuterImplicit pass) -> HsOuterTyVarBndrs flag pass -> HsOuterTyVarBndrs flag pass Source #
hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr (HsBndrVis pass) pass] Source #
isHsKindedTyVar :: HsTyVarBndr flag pass -> Bool Source #
Does this HsTyVarBndr
come with an explicit kind annotation?
hsPatSigType :: HsPatSigType pass -> LHsType pass Source #