module GHC.Types.TyThing
( TyThing (..)
, MonadThings (..)
, mkATyCon
, mkAnId
, pprShortTyThing
, pprTyThingCategory
, tyThingCategory
, implicitTyThings
, implicitConLikeThings
, implicitClassThings
, implicitTyConThings
, implicitCoTyCon
, isImplicitTyThing
, tyThingParent_maybe
, tyThingsTyCoVars
, tyThingAvailInfo
, tyThingTyCon
, tyThingCoAxiom
, tyThingDataCon
, tyThingConLike
, tyThingId
)
where
import GHC.Prelude
import GHC.Types.Name
import GHC.Types.Var
import GHC.Types.Var.Set
import GHC.Types.Id
import GHC.Types.Id.Info
import GHC.Types.Avail
import GHC.Core.Class
import GHC.Core.DataCon
import GHC.Core.ConLike
import GHC.Core.PatSyn
import GHC.Core.TyCo.FVs
import GHC.Core.TyCon
import GHC.Core.Coercion.Axiom
import GHC.Utils.Outputable
import GHC.Utils.Misc
import GHC.Utils.Panic
import Control.Monad ( liftM )
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Class
data TyThing
= AnId Id
| AConLike ConLike
| ATyCon TyCon
| ACoAxiom (CoAxiom Branched)
instance Outputable TyThing where
ppr = pprShortTyThing
instance NamedThing TyThing where
getName (AnId id) = getName id
getName (ATyCon tc) = getName tc
getName (ACoAxiom cc) = getName cc
getName (AConLike cl) = conLikeName cl
mkATyCon :: TyCon -> TyThing
mkATyCon = ATyCon
mkAnId :: Id -> TyThing
mkAnId = AnId
pprShortTyThing :: TyThing -> SDoc
pprShortTyThing thing
= pprTyThingCategory thing <+> quotes (ppr (getName thing))
pprTyThingCategory :: TyThing -> SDoc
pprTyThingCategory = text . capitalise . tyThingCategory
tyThingCategory :: TyThing -> String
tyThingCategory (ATyCon tc)
| isClassTyCon tc = "class"
| otherwise = "type constructor"
tyThingCategory (ACoAxiom _) = "coercion axiom"
tyThingCategory (AnId _) = "identifier"
tyThingCategory (AConLike (RealDataCon _)) = "data constructor"
tyThingCategory (AConLike (PatSynCon _)) = "pattern synonym"
implicitTyThings :: TyThing -> [TyThing]
implicitTyThings (AnId _) = []
implicitTyThings (ACoAxiom _cc) = []
implicitTyThings (ATyCon tc) = implicitTyConThings tc
implicitTyThings (AConLike cl) = implicitConLikeThings cl
implicitConLikeThings :: ConLike -> [TyThing]
implicitConLikeThings (RealDataCon dc)
= dataConImplicitTyThings dc
implicitConLikeThings (PatSynCon {})
= []
implicitClassThings :: Class -> [TyThing]
implicitClassThings cl
=
map ATyCon (classATs cl) ++
map AnId (classAllSelIds cl)
implicitTyConThings :: TyCon -> [TyThing]
implicitTyConThings tc
= class_stuff ++
implicitCoTyCon tc ++
[ thing | dc <- tyConDataCons tc
, thing <- AConLike (RealDataCon dc) : dataConImplicitTyThings dc ]
where
class_stuff = case tyConClass_maybe tc of
Nothing -> []
Just cl -> implicitClassThings cl
implicitCoTyCon :: TyCon -> [TyThing]
implicitCoTyCon tc
| Just co <- newTyConCo_maybe tc = [ACoAxiom $ toBranchedAxiom co]
| Just co <- isClosedSynFamilyTyConWithAxiom_maybe tc
= [ACoAxiom co]
| otherwise = []
isImplicitTyThing :: TyThing -> Bool
isImplicitTyThing (AConLike cl) = case cl of
RealDataCon {} -> True
PatSynCon {} -> False
isImplicitTyThing (AnId id) = isImplicitId id
isImplicitTyThing (ATyCon tc) = isImplicitTyCon tc
isImplicitTyThing (ACoAxiom ax) = isImplicitCoAxiom ax
tyThingParent_maybe :: TyThing -> Maybe TyThing
tyThingParent_maybe (AConLike cl) = case cl of
RealDataCon dc -> Just (ATyCon (dataConTyCon dc))
PatSynCon{} -> Nothing
tyThingParent_maybe (ATyCon tc) = case tyConAssoc_maybe tc of
Just tc -> Just (ATyCon tc)
Nothing -> Nothing
tyThingParent_maybe (AnId id) = case idDetails id of
RecSelId { sel_tycon = RecSelData tc } ->
Just (ATyCon tc)
ClassOpId cls ->
Just (ATyCon (classTyCon cls))
_other -> Nothing
tyThingParent_maybe _other = Nothing
tyThingsTyCoVars :: [TyThing] -> TyCoVarSet
tyThingsTyCoVars tts =
unionVarSets $ map ttToVarSet tts
where
ttToVarSet (AnId id) = tyCoVarsOfType $ idType id
ttToVarSet (AConLike cl) = case cl of
RealDataCon dc -> tyCoVarsOfType $ dataConRepType dc
PatSynCon{} -> emptyVarSet
ttToVarSet (ATyCon tc)
= case tyConClass_maybe tc of
Just cls -> (mkVarSet . fst . classTvsFds) cls
Nothing -> tyCoVarsOfType $ tyConKind tc
ttToVarSet (ACoAxiom _) = emptyVarSet
tyThingAvailInfo :: TyThing -> [AvailInfo]
tyThingAvailInfo (ATyCon t)
= case tyConClass_maybe t of
Just c -> [availTC n ((n : map getName (classMethods c)
++ map getName (classATs c))) [] ]
where n = getName c
Nothing -> [availTC n (n : map getName dcs) flds]
where n = getName t
dcs = tyConDataCons t
flds = tyConFieldLabels t
tyThingAvailInfo (AConLike (PatSynCon p))
= avail (getName p) : map availField (patSynFieldLabels p)
tyThingAvailInfo t
= [avail (getName t)]
tyThingTyCon :: HasDebugCallStack => TyThing -> TyCon
tyThingTyCon (ATyCon tc) = tc
tyThingTyCon other = pprPanic "tyThingTyCon" (ppr other)
tyThingCoAxiom :: HasDebugCallStack => TyThing -> CoAxiom Branched
tyThingCoAxiom (ACoAxiom ax) = ax
tyThingCoAxiom other = pprPanic "tyThingCoAxiom" (ppr other)
tyThingDataCon :: HasDebugCallStack => TyThing -> DataCon
tyThingDataCon (AConLike (RealDataCon dc)) = dc
tyThingDataCon other = pprPanic "tyThingDataCon" (ppr other)
tyThingConLike :: HasDebugCallStack => TyThing -> ConLike
tyThingConLike (AConLike dc) = dc
tyThingConLike other = pprPanic "tyThingConLike" (ppr other)
tyThingId :: HasDebugCallStack => TyThing -> Id
tyThingId (AnId id) = id
tyThingId (AConLike (RealDataCon dc)) = dataConWrapId dc
tyThingId other = pprPanic "tyThingId" (ppr other)
class Monad m => MonadThings m where
lookupThing :: Name -> m TyThing
lookupId :: Name -> m Id
lookupId = liftM tyThingId . lookupThing
lookupDataCon :: Name -> m DataCon
lookupDataCon = liftM tyThingDataCon . lookupThing
lookupTyCon :: Name -> m TyCon
lookupTyCon = liftM tyThingTyCon . lookupThing
instance MonadThings m => MonadThings (ReaderT s m) where
lookupThing = lift . lookupThing