Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data HsType pass
- = HsForAllTy {
- hst_bndrs :: [LHsTyVarBndr pass]
- hst_body :: LHsType pass
- | HsQualTy {
- hst_ctxt :: LHsContext pass
- hst_body :: LHsType pass
- | HsTyVar Promoted (Located (IdP pass))
- | HsAppsTy [LHsAppType pass]
- | HsAppTy (LHsType pass) (LHsType pass)
- | HsFunTy (LHsType pass) (LHsType pass)
- | HsListTy (LHsType pass)
- | HsPArrTy (LHsType pass)
- | HsTupleTy HsTupleSort [LHsType pass]
- | HsSumTy [LHsType pass]
- | HsOpTy (LHsType pass) (Located (IdP pass)) (LHsType pass)
- | HsParTy (LHsType pass)
- | HsIParamTy (Located HsIPName) (LHsType pass)
- | HsEqTy (LHsType pass) (LHsType pass)
- | HsKindSig (LHsType pass) (LHsKind pass)
- | HsSpliceTy (HsSplice pass) (PostTc pass Kind)
- | HsDocTy (LHsType pass) LHsDocString
- | HsBangTy HsSrcBang (LHsType pass)
- | HsRecTy [LConDeclField pass]
- | HsCoreTy Type
- | HsExplicitListTy Promoted (PostTc pass Kind) [LHsType pass]
- | HsExplicitTupleTy [PostTc pass Kind] [LHsType pass]
- | HsTyLit HsTyLit
- | HsWildCardTy (HsWildCardInfo pass)
- = HsForAllTy {
- type LHsType pass = Located (HsType pass)
- type HsKind pass = HsType pass
- type LHsKind pass = Located (HsKind pass)
- data HsTyVarBndr pass
- type LHsTyVarBndr pass = Located (HsTyVarBndr pass)
- data LHsQTyVars pass = HsQTvs {
- hsq_implicit :: PostRn pass [Name]
- hsq_explicit :: [LHsTyVarBndr pass]
- hsq_dependent :: PostRn pass NameSet
- data HsImplicitBndrs pass thing = HsIB {}
- data HsWildCardBndrs pass thing = HsWC {}
- type LHsSigType pass = HsImplicitBndrs pass (LHsType pass)
- type LHsSigWcType pass = HsWildCardBndrs pass (LHsSigType pass)
- type LHsWcType pass = HsWildCardBndrs pass (LHsType pass)
- data HsTupleSort
- data Promoted
- type HsContext pass = [LHsType pass]
- type LHsContext pass = Located (HsContext pass)
- data HsTyLit
- newtype HsIPName = HsIPName FastString
- hsIPNameFS :: HsIPName -> FastString
- data HsAppType pass
- = HsAppInfix (Located (IdP pass))
- | HsAppPrefix (LHsType pass)
- type LHsAppType pass = Located (HsAppType pass)
- type LBangType pass = Located (BangType pass)
- type BangType pass = HsType pass
- data HsSrcBang = HsSrcBang SourceText SrcUnpackedness SrcStrictness
- data HsImplBang
- data SrcStrictness
- data SrcUnpackedness
- getBangType :: LHsType a -> LHsType a
- getBangStrictness :: LHsType a -> HsSrcBang
- data ConDeclField pass = ConDeclField {
- cd_fld_names :: [LFieldOcc pass]
- cd_fld_type :: LBangType pass
- cd_fld_doc :: Maybe LHsDocString
- type LConDeclField pass = Located (ConDeclField pass)
- pprConDeclFields :: (SourceTextX pass, OutputableBndrId pass) => [LConDeclField pass] -> SDoc
- updateGadtResult :: Monad m => (SDoc -> m ()) -> SDoc -> HsConDetails (LHsType GhcRn) (Located [LConDeclField GhcRn]) -> LHsType GhcRn -> m (HsConDetails (LHsType GhcRn) (Located [LConDeclField GhcRn]), LHsType GhcRn)
- data HsConDetails arg rec
- data FieldOcc pass = FieldOcc {
- rdrNameFieldOcc :: Located RdrName
- selectorFieldOcc :: PostRn pass (IdP pass)
- type LFieldOcc pass = Located (FieldOcc pass)
- mkFieldOcc :: Located RdrName -> FieldOcc GhcPs
- data AmbiguousFieldOcc pass
- mkAmbiguousFieldOcc :: Located RdrName -> AmbiguousFieldOcc GhcPs
- rdrNameAmbiguousFieldOcc :: AmbiguousFieldOcc pass -> RdrName
- selectorAmbiguousFieldOcc :: AmbiguousFieldOcc GhcTc -> Id
- unambiguousFieldOcc :: AmbiguousFieldOcc GhcTc -> FieldOcc GhcTc
- ambiguousFieldOcc :: FieldOcc pass -> AmbiguousFieldOcc pass
- newtype HsWildCardInfo pass = AnonWildCard (PostRn pass (Located Name))
- mkAnonWildCardTy :: HsType GhcPs
- wildCardName :: HsWildCardInfo GhcRn -> Name
- sameWildCard :: Located (HsWildCardInfo pass) -> Located (HsWildCardInfo pass) -> Bool
- mkHsImplicitBndrs :: thing -> HsImplicitBndrs GhcPs thing
- mkHsWildCardBndrs :: thing -> HsWildCardBndrs GhcPs thing
- hsImplicitBody :: HsImplicitBndrs pass thing -> thing
- mkEmptyImplicitBndrs :: thing -> HsImplicitBndrs GhcRn thing
- mkEmptyWildCardBndrs :: thing -> HsWildCardBndrs GhcRn thing
- mkHsQTvs :: [LHsTyVarBndr GhcPs] -> LHsQTyVars GhcPs
- hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr pass]
- emptyLHsQTvs :: LHsQTyVars GhcRn
- isEmptyLHsQTvs :: LHsQTyVars GhcRn -> Bool
- isHsKindedTyVar :: HsTyVarBndr pass -> Bool
- hsTvbAllKinded :: LHsQTyVars pass -> Bool
- hsScopedTvs :: LHsSigType GhcRn -> [Name]
- hsWcScopedTvs :: LHsSigWcType GhcRn -> [Name]
- dropWildCards :: LHsSigWcType pass -> LHsSigType pass
- hsTyVarName :: HsTyVarBndr pass -> IdP pass
- hsAllLTyVarNames :: LHsQTyVars GhcRn -> [Name]
- hsLTyVarLocNames :: LHsQTyVars pass -> [Located (IdP pass)]
- hsLTyVarName :: LHsTyVarBndr pass -> IdP pass
- hsLTyVarLocName :: LHsTyVarBndr pass -> Located (IdP pass)
- hsExplicitLTyVarNames :: LHsQTyVars pass -> [IdP pass]
- splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], LHsContext GhcRn, LHsType GhcRn)
- getLHsInstDeclHead :: LHsSigType pass -> LHsType pass
- getLHsInstDeclClass_maybe :: LHsSigType pass -> Maybe (Located (IdP pass))
- splitLHsPatSynTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, [LHsTyVarBndr pass], LHsContext pass, LHsType pass)
- splitLHsForAllTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsType pass)
- splitLHsQualTy :: LHsType pass -> (LHsContext pass, LHsType pass)
- splitLHsSigmaTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, LHsType pass)
- splitHsFunType :: LHsType GhcRn -> ([LHsType GhcRn], LHsType GhcRn)
- splitHsAppsTy :: [LHsAppType pass] -> ([[LHsType pass]], [Located (IdP pass)])
- splitHsAppTys :: LHsType GhcRn -> [LHsType GhcRn] -> (LHsType GhcRn, [LHsType GhcRn])
- getAppsTyHead_maybe :: [LHsAppType pass] -> Maybe (LHsType pass, [LHsType pass], LexicalFixity)
- hsTyGetAppHead_maybe :: LHsType pass -> Maybe (Located (IdP pass), [LHsType pass])
- mkHsOpTy :: LHsType pass -> Located (IdP pass) -> LHsType pass -> HsType pass
- mkHsAppTy :: LHsType pass -> LHsType pass -> LHsType pass
- mkHsAppTys :: LHsType pass -> [LHsType pass] -> LHsType pass
- ignoreParens :: LHsType pass -> LHsType pass
- hsSigType :: LHsSigType pass -> LHsType pass
- hsSigWcType :: LHsSigWcType pass -> LHsType pass
- hsLTyVarBndrToType :: LHsTyVarBndr pass -> LHsType pass
- hsLTyVarBndrsToTypes :: LHsQTyVars pass -> [LHsType pass]
- pprHsType :: (SourceTextX pass, OutputableBndrId pass) => HsType pass -> SDoc
- pprHsForAll :: (SourceTextX pass, OutputableBndrId pass) => [LHsTyVarBndr pass] -> LHsContext pass -> SDoc
- pprHsForAllTvs :: (SourceTextX pass, OutputableBndrId pass) => [LHsTyVarBndr pass] -> SDoc
- pprHsForAllExtra :: (SourceTextX pass, OutputableBndrId pass) => Maybe SrcSpan -> [LHsTyVarBndr pass] -> LHsContext pass -> SDoc
- pprHsContext :: (SourceTextX pass, OutputableBndrId pass) => HsContext pass -> SDoc
- pprHsContextNoArrow :: (SourceTextX pass, OutputableBndrId pass) => HsContext pass -> SDoc
- pprHsContextMaybe :: (SourceTextX pass, OutputableBndrId pass) => HsContext pass -> Maybe SDoc
- isCompoundHsType :: LHsType pass -> Bool
- parenthesizeCompoundHsType :: LHsType pass -> LHsType pass
Documentation
Haskell Type
Instances
DataId pass => Data (HsType pass) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsType pass -> c (HsType pass) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsType pass) Source # toConstr :: HsType pass -> Constr Source # dataTypeOf :: HsType pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsType pass)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsType pass)) Source # gmapT :: (forall b. Data b => b -> b) -> HsType pass -> HsType pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsType pass -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsType pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsType pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsType pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsType pass -> m (HsType pass) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType pass -> m (HsType pass) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsType pass -> m (HsType pass) Source # | |
(SourceTextX pass, OutputableBndrId pass) => Outputable (HsType pass) Source # | |
= Located (HsType pass) | May have |
Located Haskell Type
data HsTyVarBndr pass Source #
Haskell Type Variable Binder
Instances
DataId pass => Data (HsTyVarBndr pass) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyVarBndr pass -> c (HsTyVarBndr pass) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsTyVarBndr pass) Source # toConstr :: HsTyVarBndr pass -> Constr Source # dataTypeOf :: HsTyVarBndr pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsTyVarBndr pass)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsTyVarBndr pass)) Source # gmapT :: (forall b. Data b => b -> b) -> HsTyVarBndr pass -> HsTyVarBndr pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr pass -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyVarBndr pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTyVarBndr pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyVarBndr pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyVarBndr pass -> m (HsTyVarBndr pass) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr pass -> m (HsTyVarBndr pass) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyVarBndr pass -> m (HsTyVarBndr pass) Source # | |
(SourceTextX pass, OutputableBndrId pass) => Outputable (HsTyVarBndr pass) Source # | |
type LHsTyVarBndr pass = Located (HsTyVarBndr pass) Source #
Located Haskell Type Variable Binder
data LHsQTyVars pass Source #
Located Haskell Quantified Type Variables
HsQTvs | |
|
Instances
DataId pass => Data (LHsQTyVars pass) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LHsQTyVars pass -> c (LHsQTyVars pass) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LHsQTyVars pass) Source # toConstr :: LHsQTyVars pass -> Constr Source # dataTypeOf :: LHsQTyVars pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LHsQTyVars pass)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LHsQTyVars pass)) Source # gmapT :: (forall b. Data b => b -> b) -> LHsQTyVars pass -> LHsQTyVars pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars pass -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LHsQTyVars pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LHsQTyVars pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LHsQTyVars pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LHsQTyVars pass -> m (LHsQTyVars pass) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars pass -> m (LHsQTyVars pass) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LHsQTyVars pass -> m (LHsQTyVars pass) Source # | |
(SourceTextX pass, OutputableBndrId pass) => Outputable (LHsQTyVars pass) Source # | |
data HsImplicitBndrs pass thing Source #
Haskell Implicit Binders
Instances
(DataId pass, Data thing) => Data (HsImplicitBndrs pass thing) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplicitBndrs pass thing -> c (HsImplicitBndrs pass thing) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsImplicitBndrs pass thing) Source # toConstr :: HsImplicitBndrs pass thing -> Constr Source # dataTypeOf :: HsImplicitBndrs pass thing -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsImplicitBndrs pass thing)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsImplicitBndrs pass thing)) Source # gmapT :: (forall b. Data b => b -> b) -> HsImplicitBndrs pass thing -> HsImplicitBndrs pass thing Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs pass thing -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplicitBndrs pass thing -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsImplicitBndrs pass thing -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplicitBndrs pass thing -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplicitBndrs pass thing -> m (HsImplicitBndrs pass thing) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs pass thing -> m (HsImplicitBndrs pass thing) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplicitBndrs pass thing -> m (HsImplicitBndrs pass thing) Source # | |
Outputable thing => Outputable (HsImplicitBndrs pass thing) Source # | |
data HsWildCardBndrs pass thing Source #
Haskell Wildcard Binders
Instances
(DataId pass, Data thing) => Data (HsWildCardBndrs pass thing) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardBndrs pass thing -> c (HsWildCardBndrs pass thing) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardBndrs pass thing) Source # toConstr :: HsWildCardBndrs pass thing -> Constr Source # dataTypeOf :: HsWildCardBndrs pass thing -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardBndrs pass thing)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardBndrs pass thing)) Source # gmapT :: (forall b. Data b => b -> b) -> HsWildCardBndrs pass thing -> HsWildCardBndrs pass thing Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs pass thing -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardBndrs pass thing -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardBndrs pass thing -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardBndrs pass thing -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardBndrs pass thing -> m (HsWildCardBndrs pass thing) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs pass thing -> m (HsWildCardBndrs pass thing) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardBndrs pass thing -> m (HsWildCardBndrs pass thing) Source # | |
Outputable thing => Outputable (HsWildCardBndrs pass thing) Source # | |
type LHsSigType pass = HsImplicitBndrs pass (LHsType 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
data HsTupleSort Source #
Haskell Tuple Sort
Instances
Data HsTupleSort Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTupleSort -> c HsTupleSort Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTupleSort Source # toConstr :: HsTupleSort -> Constr Source # dataTypeOf :: HsTupleSort -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTupleSort) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTupleSort) Source # gmapT :: (forall b. Data b => b -> b) -> HsTupleSort -> HsTupleSort Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTupleSort -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTupleSort -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTupleSort -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTupleSort -> m HsTupleSort Source # |
Promoted data types.
Instances
Eq Promoted Source # | |
Data Promoted Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Promoted -> c Promoted Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Promoted Source # toConstr :: Promoted -> Constr Source # dataTypeOf :: Promoted -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Promoted) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Promoted) Source # gmapT :: (forall b. Data b => b -> b) -> Promoted -> Promoted Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Promoted -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Promoted -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Promoted -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Promoted -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Promoted -> m Promoted Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Promoted -> m Promoted Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Promoted -> m Promoted Source # | |
Show Promoted Source # | |
Haskell Type Literal
Instances
Data HsTyLit Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsTyLit -> c HsTyLit Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsTyLit Source # toConstr :: HsTyLit -> Constr Source # dataTypeOf :: HsTyLit -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsTyLit) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsTyLit) Source # gmapT :: (forall b. Data b => b -> b) -> HsTyLit -> HsTyLit Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsTyLit -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsTyLit -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsTyLit -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsTyLit -> m HsTyLit Source # | |
Outputable HsTyLit Source # | |
These names are used early on to store the names of implicit parameters. They completely disappear after type-checking.
Instances
Eq HsIPName Source # | |
Data HsIPName Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsIPName -> c HsIPName Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsIPName Source # toConstr :: HsIPName -> Constr Source # dataTypeOf :: HsIPName -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsIPName) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsIPName) Source # gmapT :: (forall b. Data b => b -> b) -> HsIPName -> HsIPName Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsIPName -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsIPName -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsIPName -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsIPName -> m HsIPName Source # | |
OutputableBndr HsIPName Source # | |
Outputable HsIPName Source # | |
hsIPNameFS :: HsIPName -> FastString Source #
Haskell Application Type
HsAppInfix (Located (IdP pass)) | |
HsAppPrefix (LHsType pass) |
Instances
DataId pass => Data (HsAppType pass) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsAppType pass -> c (HsAppType pass) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsAppType pass) Source # toConstr :: HsAppType pass -> Constr Source # dataTypeOf :: HsAppType pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsAppType pass)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsAppType pass)) Source # gmapT :: (forall b. Data b => b -> b) -> HsAppType pass -> HsAppType pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsAppType pass -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsAppType pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsAppType pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsAppType pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsAppType pass -> m (HsAppType pass) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsAppType pass -> m (HsAppType pass) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsAppType pass -> m (HsAppType pass) Source # | |
(SourceTextX pass, OutputableBndrId pass) => Outputable (HsAppType pass) Source # | |
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
Data HsSrcBang Source # | |
Defined in DataCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsSrcBang Source # toConstr :: HsSrcBang -> Constr Source # dataTypeOf :: HsSrcBang -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsSrcBang) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang) Source # gmapT :: (forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsSrcBang -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSrcBang -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang Source # | |
Outputable HsSrcBang Source # | |
data HsImplBang Source #
Haskell Implementation Bang
Bangs of data constructor arguments as generated by the compiler after consulting HsSrcBang, flags, etc.
HsLazy | Lazy field, or one with an unlifted type |
HsStrict | Strict but not unpacked field |
HsUnpack (Maybe Coercion) | Strict and unpacked field co :: arg-ty ~ product-ty HsBang |
Instances
Data HsImplBang Source # | |
Defined in DataCon gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplBang -> c HsImplBang Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsImplBang Source # toConstr :: HsImplBang -> Constr Source # dataTypeOf :: HsImplBang -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HsImplBang) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImplBang) Source # gmapT :: (forall b. Data b => b -> b) -> HsImplBang -> HsImplBang Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsImplBang -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplBang -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang Source # | |
Outputable HsImplBang Source # | |
data SrcStrictness Source #
Source Strictness
What strictness annotation the user wrote
SrcLazy | Lazy, ie '~' |
SrcStrict | Strict, ie |
NoSrcStrict | no strictness annotation |
Instances
data SrcUnpackedness Source #
Source Unpackedness
What unpackedness the user requested
SrcUnpack | |
SrcNoUnpack | |
NoSrcUnpack | no unpack pragma |
Instances
getBangType :: LHsType a -> LHsType a Source #
getBangStrictness :: LHsType a -> HsSrcBang Source #
data ConDeclField pass Source #
Constructor Declaration Field
ConDeclField | |
|
Instances
DataId pass => Data (ConDeclField pass) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConDeclField pass -> c (ConDeclField pass) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ConDeclField pass) Source # toConstr :: ConDeclField pass -> Constr Source # dataTypeOf :: ConDeclField pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ConDeclField pass)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ConDeclField pass)) Source # gmapT :: (forall b. Data b => b -> b) -> ConDeclField pass -> ConDeclField pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField pass -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConDeclField pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ConDeclField pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConDeclField pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConDeclField pass -> m (ConDeclField pass) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField pass -> m (ConDeclField pass) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConDeclField pass -> m (ConDeclField pass) Source # | |
(SourceTextX pass, OutputableBndrId pass) => Outputable (ConDeclField pass) Source # | |
type LConDeclField pass Source #
= Located (ConDeclField pass) | May have |
Located Constructor Declaration Field
pprConDeclFields :: (SourceTextX pass, OutputableBndrId pass) => [LConDeclField pass] -> SDoc Source #
:: Monad m | |
=> (SDoc -> m ()) | |
-> SDoc | |
-> HsConDetails (LHsType GhcRn) (Located [LConDeclField GhcRn]) | Original details |
-> LHsType GhcRn | Original result type |
-> m (HsConDetails (LHsType GhcRn) (Located [LConDeclField GhcRn]), LHsType GhcRn) |
data HsConDetails arg rec Source #
Haskell Constructor Details
Instances
(Data arg, Data rec) => Data (HsConDetails arg rec) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConDetails arg rec -> c (HsConDetails arg rec) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConDetails arg rec) Source # toConstr :: HsConDetails arg rec -> Constr Source # dataTypeOf :: HsConDetails arg rec -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConDetails arg rec)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConDetails arg rec)) Source # gmapT :: (forall b. Data b => b -> b) -> HsConDetails arg rec -> HsConDetails arg rec Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails arg rec -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConDetails arg rec -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsConDetails arg rec -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConDetails arg rec -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConDetails arg rec -> m (HsConDetails arg rec) Source # | |
(Outputable arg, Outputable rec) => Outputable (HsConDetails arg rec) Source # | |
Field Occurrence
Represents an *occurrence* of an unambiguous field. We store
both the RdrName
the user originally wrote, and after the
renamer, the selector function.
FieldOcc | |
|
Instances
Eq (PostRn pass (IdP pass)) => Eq (FieldOcc pass) Source # | |
DataId pass => Data (FieldOcc pass) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldOcc pass -> c (FieldOcc pass) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldOcc pass) Source # toConstr :: FieldOcc pass -> Constr Source # dataTypeOf :: FieldOcc pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FieldOcc pass)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldOcc pass)) Source # gmapT :: (forall b. Data b => b -> b) -> FieldOcc pass -> FieldOcc pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc pass -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldOcc pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> FieldOcc pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldOcc pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldOcc pass -> m (FieldOcc pass) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc pass -> m (FieldOcc pass) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldOcc pass -> m (FieldOcc pass) Source # | |
Ord (PostRn pass (IdP pass)) => Ord (FieldOcc pass) Source # | |
Defined in HsTypes compare :: FieldOcc pass -> FieldOcc pass -> Ordering # (<) :: FieldOcc pass -> FieldOcc pass -> Bool # (<=) :: FieldOcc pass -> FieldOcc pass -> Bool # (>) :: FieldOcc pass -> FieldOcc pass -> Bool # (>=) :: FieldOcc pass -> FieldOcc pass -> Bool # | |
Outputable (FieldOcc pass) Source # | |
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 HsPat and Note [Disambiguating record fields] in TcExpr. See Note [Located RdrNames] in HsExpr
Unambiguous (Located RdrName) (PostRn pass (IdP pass)) | |
Ambiguous (Located RdrName) (PostTc pass (IdP pass)) |
Instances
rdrNameAmbiguousFieldOcc :: AmbiguousFieldOcc pass -> RdrName Source #
ambiguousFieldOcc :: FieldOcc pass -> AmbiguousFieldOcc pass Source #
newtype HsWildCardInfo pass Source #
AnonWildCard (PostRn pass (Located Name)) |
Instances
DataId pass => Data (HsWildCardInfo pass) Source # | |
Defined in HsTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWildCardInfo pass -> c (HsWildCardInfo pass) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsWildCardInfo pass) Source # toConstr :: HsWildCardInfo pass -> Constr Source # dataTypeOf :: HsWildCardInfo pass -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsWildCardInfo pass)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsWildCardInfo pass)) Source # gmapT :: (forall b. Data b => b -> b) -> HsWildCardInfo pass -> HsWildCardInfo pass Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardInfo pass -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWildCardInfo pass -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsWildCardInfo pass -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWildCardInfo pass -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWildCardInfo pass -> m (HsWildCardInfo pass) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardInfo pass -> m (HsWildCardInfo pass) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWildCardInfo pass -> m (HsWildCardInfo pass) Source # | |
Outputable (HsWildCardInfo pass) Source # | |
wildCardName :: HsWildCardInfo GhcRn -> Name Source #
sameWildCard :: Located (HsWildCardInfo pass) -> Located (HsWildCardInfo pass) -> Bool Source #
mkHsImplicitBndrs :: thing -> HsImplicitBndrs GhcPs thing Source #
mkHsWildCardBndrs :: thing -> HsWildCardBndrs GhcPs thing Source #
hsImplicitBody :: HsImplicitBndrs pass thing -> thing Source #
mkEmptyImplicitBndrs :: thing -> HsImplicitBndrs GhcRn thing Source #
mkEmptyWildCardBndrs :: thing -> HsWildCardBndrs GhcRn thing Source #
mkHsQTvs :: [LHsTyVarBndr GhcPs] -> LHsQTyVars GhcPs Source #
hsQTvExplicit :: LHsQTyVars pass -> [LHsTyVarBndr pass] Source #
isEmptyLHsQTvs :: LHsQTyVars GhcRn -> Bool Source #
isHsKindedTyVar :: HsTyVarBndr pass -> Bool Source #
Does this HsTyVarBndr
come with an explicit kind annotation?
hsTvbAllKinded :: LHsQTyVars pass -> Bool Source #
Do all type variables in this LHsQTyVars
come with kind annotations?
hsScopedTvs :: LHsSigType GhcRn -> [Name] Source #
hsWcScopedTvs :: LHsSigWcType GhcRn -> [Name] Source #
dropWildCards :: LHsSigWcType pass -> LHsSigType pass Source #
hsTyVarName :: HsTyVarBndr pass -> IdP pass Source #
hsAllLTyVarNames :: LHsQTyVars GhcRn -> [Name] Source #
hsLTyVarLocNames :: LHsQTyVars pass -> [Located (IdP pass)] Source #
hsLTyVarName :: LHsTyVarBndr pass -> IdP pass Source #
hsLTyVarLocName :: LHsTyVarBndr pass -> Located (IdP pass) Source #
hsExplicitLTyVarNames :: LHsQTyVars pass -> [IdP pass] Source #
splitLHsInstDeclTy :: LHsSigType GhcRn -> ([Name], LHsContext GhcRn, LHsType GhcRn) Source #
getLHsInstDeclHead :: LHsSigType pass -> LHsType pass Source #
getLHsInstDeclClass_maybe :: LHsSigType pass -> Maybe (Located (IdP pass)) Source #
splitLHsPatSynTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, [LHsTyVarBndr pass], LHsContext pass, LHsType pass) Source #
splitLHsForAllTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsType pass) Source #
splitLHsQualTy :: LHsType pass -> (LHsContext pass, LHsType pass) Source #
splitLHsSigmaTy :: LHsType pass -> ([LHsTyVarBndr pass], LHsContext pass, LHsType pass) Source #
splitHsAppsTy :: [LHsAppType pass] -> ([[LHsType pass]], [Located (IdP pass)]) Source #
Splits a [HsAppType pass] (the payload of an HsAppsTy) into regions of
prefix types (normal types) and infix operators.
If splitHsAppsTy tys = (non_syms, syms)
, then tys
starts with the first
element of non_syms
followed by the first element of syms
followed by
the next element of non_syms
, etc. It is guaranteed that the non_syms list
has one more element than the syms list.
getAppsTyHead_maybe :: [LHsAppType pass] -> Maybe (LHsType pass, [LHsType pass], LexicalFixity) Source #
Retrieves the head of an HsAppsTy, if this can be done unambiguously, without consulting fixities.
ignoreParens :: LHsType pass -> LHsType pass Source #
hsSigType :: LHsSigType pass -> LHsType pass Source #
hsSigWcType :: LHsSigWcType pass -> LHsType pass Source #
hsLTyVarBndrToType :: LHsTyVarBndr pass -> LHsType pass Source #
Convert a LHsTyVarBndr to an equivalent LHsType.
hsLTyVarBndrsToTypes :: LHsQTyVars pass -> [LHsType pass] Source #
Convert a LHsTyVarBndrs to a list of types. Works on *type* variable only, no kind vars.
pprHsType :: (SourceTextX pass, OutputableBndrId pass) => HsType pass -> SDoc Source #
pprHsForAll :: (SourceTextX pass, OutputableBndrId pass) => [LHsTyVarBndr pass] -> LHsContext pass -> SDoc Source #
pprHsForAllTvs :: (SourceTextX pass, OutputableBndrId pass) => [LHsTyVarBndr pass] -> SDoc Source #
pprHsForAllExtra :: (SourceTextX pass, OutputableBndrId pass) => Maybe SrcSpan -> [LHsTyVarBndr pass] -> LHsContext pass -> SDoc Source #
Version of pprHsForAll
that can also print an extra-constraints
wildcard, e.g. _ => a -> Bool
or (Show a, _) => a -> String
. This
underscore will be printed when the 'Maybe SrcSpan' argument is a Just
containing the location of the extra-constraints wildcard. A special
function for this is needed, as the extra-constraints wildcard is removed
from the actual context and type, and stored in a separate field, thus just
printing the type will not print the extra-constraints wildcard.
pprHsContext :: (SourceTextX pass, OutputableBndrId pass) => HsContext pass -> SDoc Source #
pprHsContextNoArrow :: (SourceTextX pass, OutputableBndrId pass) => HsContext pass -> SDoc Source #
pprHsContextMaybe :: (SourceTextX pass, OutputableBndrId pass) => HsContext pass -> Maybe SDoc Source #
isCompoundHsType :: LHsType pass -> Bool Source #
Return True
for compound types that will need parentheses when used in
an argument position.
parenthesizeCompoundHsType :: LHsType pass -> LHsType pass Source #
checks if parenthesizeCompoundHsType
ty
is
true, and if so, surrounds isCompoundHsType
tyty
with an HsParTy
. Otherwise, it simply
returns ty
.