{-# OPTIONS_HADDOCK not-home #-}
{-# LANGUAGE CPP, DeriveDataTypeable, MultiWayIf, PatternSynonyms, BangPatterns #-}
module GHC.Core.TyCo.Rep (
TyThing(..), tyThingCategory, pprTyThingCategory, pprShortTyThing,
Type( TyVarTy, AppTy, TyConApp, ForAllTy
, LitTy, CastTy, CoercionTy
, FunTy, ft_arg, ft_res, ft_af
),
TyLit(..),
KindOrType, Kind,
KnotTied,
PredType, ThetaType,
ArgFlag(..), AnonArgFlag(..), ForallVisFlag(..),
Coercion(..),
UnivCoProvenance(..),
CoercionHole(..), BlockSubstFlag(..), coHoleCoVar, setCoHoleCoVar,
CoercionN, CoercionR, CoercionP, KindCoercion,
MCoercion(..), MCoercionR, MCoercionN,
mkTyConTy, mkTyVarTy, mkTyVarTys,
mkTyCoVarTy, mkTyCoVarTys,
mkFunTy, mkVisFunTy, mkInvisFunTy, mkVisFunTys, mkInvisFunTys,
mkForAllTy, mkForAllTys, mkInvisForAllTys,
mkPiTy, mkPiTys,
TyCoBinder(..), TyCoVarBinder, TyBinder,
binderVar, binderVars, binderType, binderArgFlag,
delBinderVar,
isInvisibleArgFlag, isVisibleArgFlag,
isInvisibleBinder, isVisibleBinder,
isTyBinder, isNamedBinder,
pickLR,
TyCoFolder(..), foldTyCo,
typeSize, coercionSize, provSize
) where
#include "HsVersions.h"
import GHC.Prelude
import {-# SOURCE #-} GHC.Core.TyCo.Ppr ( pprType, pprCo, pprTyLit )
import {-# SOURCE #-} GHC.Core.ConLike ( ConLike(..), conLikeName )
import GHC.Iface.Type
import GHC.Types.Var
import GHC.Types.Var.Set
import GHC.Types.Name hiding ( varName )
import GHC.Core.TyCon
import GHC.Core.Coercion.Axiom
import GHC.Types.Basic ( LeftOrRight(..), pickLR )
import GHC.Utils.Outputable
import GHC.Data.FastString
import GHC.Utils.Misc
import qualified Data.Data as Data hiding ( TyCon )
import Data.IORef ( IORef )
data TyThing
= AnId Id
| AConLike ConLike
| ATyCon TyCon
| ACoAxiom (CoAxiom Branched)
instance Outputable TyThing where
ppr :: TyThing -> SDoc
ppr = TyThing -> SDoc
pprShortTyThing
instance NamedThing TyThing where
getName :: TyThing -> Name
getName (AnId TyVar
id) = TyVar -> Name
forall a. NamedThing a => a -> Name
External instance of the constraint type NamedThing TyVar
getName TyVar
id
getName (ATyCon TyCon
tc) = TyCon -> Name
forall a. NamedThing a => a -> Name
External instance of the constraint type NamedThing TyCon
getName TyCon
tc
getName (ACoAxiom CoAxiom Branched
cc) = CoAxiom Branched -> Name
forall a. NamedThing a => a -> Name
External instance of the constraint type forall (br :: BranchFlag). NamedThing (CoAxiom br)
getName CoAxiom Branched
cc
getName (AConLike ConLike
cl) = ConLike -> Name
conLikeName ConLike
cl
pprShortTyThing :: TyThing -> SDoc
pprShortTyThing :: TyThing -> SDoc
pprShortTyThing TyThing
thing
= TyThing -> SDoc
pprTyThingCategory TyThing
thing SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
quotes (Name -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable Name
ppr (TyThing -> Name
forall a. NamedThing a => a -> Name
Instance of class: NamedThing of the constraint type NamedThing TyThing
getName TyThing
thing))
pprTyThingCategory :: TyThing -> SDoc
pprTyThingCategory :: TyThing -> SDoc
pprTyThingCategory = String -> SDoc
text (String -> SDoc) -> (TyThing -> String) -> TyThing -> SDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
capitalise (String -> String) -> (TyThing -> String) -> TyThing -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyThing -> String
tyThingCategory
tyThingCategory :: TyThing -> String
tyThingCategory :: TyThing -> String
tyThingCategory (ATyCon TyCon
tc)
| TyCon -> Bool
isClassTyCon TyCon
tc = String
"class"
| Bool
otherwise = String
"type constructor"
tyThingCategory (ACoAxiom CoAxiom Branched
_) = String
"coercion axiom"
tyThingCategory (AnId TyVar
_) = String
"identifier"
tyThingCategory (AConLike (RealDataCon DataCon
_)) = String
"data constructor"
tyThingCategory (AConLike (PatSynCon PatSyn
_)) = String
"pattern synonym"
type KindOrType = Type
type Kind = Type
data Type
= TyVarTy Var
| AppTy
Type
Type
| TyConApp
TyCon
[KindOrType]
| ForAllTy
{-# UNPACK #-} !TyCoVarBinder
Type
| FunTy
{ Type -> AnonArgFlag
ft_af :: AnonArgFlag
, Type -> Type
ft_arg :: Type
, Type -> Type
ft_res :: Type }
| LitTy TyLit
| CastTy
Type
KindCoercion
| CoercionTy
Coercion
deriving Typeable Type
DataType
Constr
Typeable Type
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type)
-> (Type -> Constr)
-> (Type -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Type))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type))
-> ((forall b. Data b => b -> b) -> Type -> Type)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r)
-> (forall u. (forall d. Data d => d -> u) -> Type -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Type -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Type -> m Type)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Type -> m Type)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Type -> m Type)
-> Data Type
Type -> DataType
Type -> Constr
(forall b. Data b => b -> b) -> Type -> Type
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Type -> u
forall u. (forall d. Data d => d -> u) -> Type -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Type -> m Type
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Type -> m Type
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Type)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type)
$cCoercionTy :: Constr
$cCastTy :: Constr
$cLitTy :: Constr
$cFunTy :: Constr
$cForAllTy :: Constr
$cTyConApp :: Constr
$cAppTy :: Constr
$cTyVarTy :: Constr
$tType :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Type -> m Type
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Type -> m Type
gmapMp :: (forall d. Data d => d -> m d) -> Type -> m Type
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Type -> m Type
gmapM :: (forall d. Data d => d -> m d) -> Type -> m Type
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Type -> m Type
gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Type -> u
gmapQ :: (forall d. Data d => d -> u) -> Type -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Type -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r
gmapT :: (forall b. Data b => b -> b) -> Type -> Type
$cgmapT :: (forall b. Data b => b -> b) -> Type -> Type
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Type)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Type)
dataTypeOf :: Type -> DataType
$cdataTypeOf :: Type -> DataType
toConstr :: Type -> Constr
$ctoConstr :: Type -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Type
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Type -> c Type
External instance of the constraint type Data ArgFlag
Instance of class: Data of the constraint type Data Coercion
External instance of the constraint type Data ArgFlag
Instance of class: Data of the constraint type Data Type
External instance of the constraint type Data TyVar
Instance of class: Data of the constraint type Data Coercion
External instance of the constraint type Data AnonArgFlag
External instance of the constraint type Data ArgFlag
External instance of the constraint type forall var argf. (Data var, Data argf) => Data (VarBndr var argf)
External instance of the constraint type Data TyCon
External instance of the constraint type forall a. Data a => Data [a]
Instance of class: Data of the constraint type Data Type
External instance of the constraint type Data TyVar
External instance of the constraint type Data TyVar
Instance of class: Data of the constraint type Data TyLit
Instance of class: Data of the constraint type Data Type
Instance of class: Data of the constraint type Data Coercion
Data.Data
instance Outputable Type where
ppr :: Type -> SDoc
ppr = Type -> SDoc
pprType
data TyLit
= NumTyLit Integer
| StrTyLit FastString
deriving (TyLit -> TyLit -> Bool
(TyLit -> TyLit -> Bool) -> (TyLit -> TyLit -> Bool) -> Eq TyLit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TyLit -> TyLit -> Bool
$c/= :: TyLit -> TyLit -> Bool
== :: TyLit -> TyLit -> Bool
$c== :: TyLit -> TyLit -> Bool
External instance of the constraint type Eq FastString
External instance of the constraint type Eq Integer
Eq, Eq TyLit
Eq TyLit
-> (TyLit -> TyLit -> Ordering)
-> (TyLit -> TyLit -> Bool)
-> (TyLit -> TyLit -> Bool)
-> (TyLit -> TyLit -> Bool)
-> (TyLit -> TyLit -> Bool)
-> (TyLit -> TyLit -> TyLit)
-> (TyLit -> TyLit -> TyLit)
-> Ord TyLit
TyLit -> TyLit -> Bool
TyLit -> TyLit -> Ordering
TyLit -> TyLit -> TyLit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TyLit -> TyLit -> TyLit
$cmin :: TyLit -> TyLit -> TyLit
max :: TyLit -> TyLit -> TyLit
$cmax :: TyLit -> TyLit -> TyLit
>= :: TyLit -> TyLit -> Bool
$c>= :: TyLit -> TyLit -> Bool
> :: TyLit -> TyLit -> Bool
$c> :: TyLit -> TyLit -> Bool
<= :: TyLit -> TyLit -> Bool
$c<= :: TyLit -> TyLit -> Bool
< :: TyLit -> TyLit -> Bool
$c< :: TyLit -> TyLit -> Bool
compare :: TyLit -> TyLit -> Ordering
$ccompare :: TyLit -> TyLit -> Ordering
External instance of the constraint type Ord FastString
External instance of the constraint type Ord Integer
Instance of class: Eq of the constraint type Eq TyLit
Instance of class: Ord of the constraint type Ord TyLit
Instance of class: Eq of the constraint type Eq TyLit
Ord, Typeable TyLit
DataType
Constr
Typeable TyLit
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyLit -> c TyLit)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyLit)
-> (TyLit -> Constr)
-> (TyLit -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TyLit))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyLit))
-> ((forall b. Data b => b -> b) -> TyLit -> TyLit)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r)
-> (forall u. (forall d. Data d => d -> u) -> TyLit -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> TyLit -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TyLit -> m TyLit)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyLit -> m TyLit)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyLit -> m TyLit)
-> Data TyLit
TyLit -> DataType
TyLit -> Constr
(forall b. Data b => b -> b) -> TyLit -> TyLit
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyLit -> c TyLit
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyLit
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TyLit -> u
forall u. (forall d. Data d => d -> u) -> TyLit -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TyLit -> m TyLit
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyLit -> m TyLit
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyLit
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyLit -> c TyLit
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TyLit)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyLit)
$cStrTyLit :: Constr
$cNumTyLit :: Constr
$tTyLit :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TyLit -> m TyLit
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyLit -> m TyLit
gmapMp :: (forall d. Data d => d -> m d) -> TyLit -> m TyLit
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyLit -> m TyLit
gmapM :: (forall d. Data d => d -> m d) -> TyLit -> m TyLit
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TyLit -> m TyLit
gmapQi :: Int -> (forall d. Data d => d -> u) -> TyLit -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TyLit -> u
gmapQ :: (forall d. Data d => d -> u) -> TyLit -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TyLit -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r
gmapT :: (forall b. Data b => b -> b) -> TyLit -> TyLit
$cgmapT :: (forall b. Data b => b -> b) -> TyLit -> TyLit
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyLit)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyLit)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TyLit)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TyLit)
dataTypeOf :: TyLit -> DataType
$cdataTypeOf :: TyLit -> DataType
toConstr :: TyLit -> Constr
$ctoConstr :: TyLit -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyLit
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyLit
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyLit -> c TyLit
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyLit -> c TyLit
External instance of the constraint type Data FastString
External instance of the constraint type Data Integer
Data.Data)
instance Outputable TyLit where
ppr :: TyLit -> SDoc
ppr = TyLit -> SDoc
pprTyLit
type KnotTied ty = ty
data TyCoBinder
= Named TyCoVarBinder
| Anon AnonArgFlag Type
deriving Typeable TyCoBinder
DataType
Constr
Typeable TyCoBinder
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyCoBinder -> c TyCoBinder)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyCoBinder)
-> (TyCoBinder -> Constr)
-> (TyCoBinder -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TyCoBinder))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TyCoBinder))
-> ((forall b. Data b => b -> b) -> TyCoBinder -> TyCoBinder)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r)
-> (forall u. (forall d. Data d => d -> u) -> TyCoBinder -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder)
-> Data TyCoBinder
TyCoBinder -> DataType
TyCoBinder -> Constr
(forall b. Data b => b -> b) -> TyCoBinder -> TyCoBinder
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyCoBinder -> c TyCoBinder
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyCoBinder
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u
forall u. (forall d. Data d => d -> u) -> TyCoBinder -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyCoBinder
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyCoBinder -> c TyCoBinder
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TyCoBinder)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCoBinder)
$cAnon :: Constr
$cNamed :: Constr
$tTyCoBinder :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder
gmapMp :: (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder
gmapM :: (forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TyCoBinder -> m TyCoBinder
gmapQi :: Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u
gmapQ :: (forall d. Data d => d -> u) -> TyCoBinder -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TyCoBinder -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TyCoBinder -> r
gmapT :: (forall b. Data b => b -> b) -> TyCoBinder -> TyCoBinder
$cgmapT :: (forall b. Data b => b -> b) -> TyCoBinder -> TyCoBinder
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCoBinder)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyCoBinder)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TyCoBinder)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TyCoBinder)
dataTypeOf :: TyCoBinder -> DataType
$cdataTypeOf :: TyCoBinder -> DataType
toConstr :: TyCoBinder -> Constr
$ctoConstr :: TyCoBinder -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyCoBinder
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TyCoBinder
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyCoBinder -> c TyCoBinder
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TyCoBinder -> c TyCoBinder
External instance of the constraint type Data ArgFlag
External instance of the constraint type Data TyVar
External instance of the constraint type Data ArgFlag
External instance of the constraint type Data TyVar
External instance of the constraint type Data ArgFlag
External instance of the constraint type Data AnonArgFlag
External instance of the constraint type forall var argf. (Data var, Data argf) => Data (VarBndr var argf)
External instance of the constraint type Data TyVar
Instance of class: Data of the constraint type Data Type
Data.Data
instance Outputable TyCoBinder where
ppr :: TyCoBinder -> SDoc
ppr (Anon AnonArgFlag
af Type
ty) = AnonArgFlag -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable AnonArgFlag
ppr AnonArgFlag
af SDoc -> SDoc -> SDoc
<+> Type -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable Type
ppr Type
ty
ppr (Named (Bndr TyVar
v ArgFlag
Required)) = TyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyVar
ppr TyVar
v
ppr (Named (Bndr TyVar
v (Invisible Specificity
spec))) = case Specificity
spec of
Specificity
SpecifiedSpec -> Char -> SDoc
char Char
'@' SDoc -> SDoc -> SDoc
<> TyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyVar
ppr TyVar
v
Specificity
InferredSpec -> SDoc -> SDoc
braces (TyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyVar
ppr TyVar
v)
type TyBinder = TyCoBinder
delBinderVar :: VarSet -> TyCoVarBinder -> VarSet
delBinderVar :: VarSet -> TyCoVarBinder -> VarSet
delBinderVar VarSet
vars (Bndr TyVar
tv ArgFlag
_) = VarSet
vars VarSet -> TyVar -> VarSet
`delVarSet` TyVar
tv
isInvisibleBinder :: TyCoBinder -> Bool
isInvisibleBinder :: TyCoBinder -> Bool
isInvisibleBinder (Named (Bndr TyVar
_ ArgFlag
vis)) = ArgFlag -> Bool
isInvisibleArgFlag ArgFlag
vis
isInvisibleBinder (Anon AnonArgFlag
InvisArg Type
_) = Bool
True
isInvisibleBinder (Anon AnonArgFlag
VisArg Type
_) = Bool
False
isVisibleBinder :: TyCoBinder -> Bool
isVisibleBinder :: TyCoBinder -> Bool
isVisibleBinder = Bool -> Bool
not (Bool -> Bool) -> (TyCoBinder -> Bool) -> TyCoBinder -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyCoBinder -> Bool
isInvisibleBinder
isNamedBinder :: TyCoBinder -> Bool
isNamedBinder :: TyCoBinder -> Bool
isNamedBinder (Named {}) = Bool
True
isNamedBinder (Anon {}) = Bool
False
isTyBinder :: TyCoBinder -> Bool
isTyBinder :: TyCoBinder -> Bool
isTyBinder (Named TyCoVarBinder
bnd) = TyCoVarBinder -> Bool
isTyVarBinder TyCoVarBinder
bnd
isTyBinder TyCoBinder
_ = Bool
True
type PredType = Type
type ThetaType = [PredType]
mkTyVarTy :: TyVar -> Type
mkTyVarTy :: TyVar -> Type
mkTyVarTy TyVar
v = ASSERT2( isTyVar v, ppr v <+> dcolon <+> ppr (tyVarKind v) )
TyVar -> Type
TyVarTy TyVar
v
mkTyVarTys :: [TyVar] -> [Type]
mkTyVarTys :: [TyVar] -> [Type]
mkTyVarTys = (TyVar -> Type) -> [TyVar] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map TyVar -> Type
mkTyVarTy
mkTyCoVarTy :: TyCoVar -> Type
mkTyCoVarTy :: TyVar -> Type
mkTyCoVarTy TyVar
v
| TyVar -> Bool
isTyVar TyVar
v
= TyVar -> Type
TyVarTy TyVar
v
| Bool
otherwise
= Coercion -> Type
CoercionTy (TyVar -> Coercion
CoVarCo TyVar
v)
mkTyCoVarTys :: [TyCoVar] -> [Type]
mkTyCoVarTys :: [TyVar] -> [Type]
mkTyCoVarTys = (TyVar -> Type) -> [TyVar] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map TyVar -> Type
mkTyCoVarTy
infixr 3 `mkFunTy`, `mkVisFunTy`, `mkInvisFunTy`
mkFunTy :: AnonArgFlag -> Type -> Type -> Type
mkFunTy :: AnonArgFlag -> Type -> Type -> Type
mkFunTy AnonArgFlag
af Type
arg Type
res = FunTy :: AnonArgFlag -> Type -> Type -> Type
FunTy { ft_af :: AnonArgFlag
ft_af = AnonArgFlag
af, ft_arg :: Type
ft_arg = Type
arg, ft_res :: Type
ft_res = Type
res }
mkVisFunTy, mkInvisFunTy :: Type -> Type -> Type
mkVisFunTy :: Type -> Type -> Type
mkVisFunTy = AnonArgFlag -> Type -> Type -> Type
mkFunTy AnonArgFlag
VisArg
mkInvisFunTy :: Type -> Type -> Type
mkInvisFunTy = AnonArgFlag -> Type -> Type -> Type
mkFunTy AnonArgFlag
InvisArg
mkVisFunTys, mkInvisFunTys :: [Type] -> Type -> Type
mkVisFunTys :: [Type] -> Type -> Type
mkVisFunTys [Type]
tys Type
ty = (Type -> Type -> Type) -> Type -> [Type] -> Type
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr Type -> Type -> Type
mkVisFunTy Type
ty [Type]
tys
mkInvisFunTys :: [Type] -> Type -> Type
mkInvisFunTys [Type]
tys Type
ty = (Type -> Type -> Type) -> Type -> [Type] -> Type
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr Type -> Type -> Type
mkInvisFunTy Type
ty [Type]
tys
mkForAllTy :: TyCoVar -> ArgFlag -> Type -> Type
mkForAllTy :: TyVar -> ArgFlag -> Type -> Type
mkForAllTy TyVar
tv ArgFlag
vis Type
ty = TyCoVarBinder -> Type -> Type
ForAllTy (TyVar -> ArgFlag -> TyCoVarBinder
forall var argf. var -> argf -> VarBndr var argf
Bndr TyVar
tv ArgFlag
vis) Type
ty
mkForAllTys :: [TyCoVarBinder] -> Type -> Type
mkForAllTys :: [TyCoVarBinder] -> Type -> Type
mkForAllTys [TyCoVarBinder]
tyvars Type
ty = (TyCoVarBinder -> Type -> Type) -> Type -> [TyCoVarBinder] -> Type
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr TyCoVarBinder -> Type -> Type
ForAllTy Type
ty [TyCoVarBinder]
tyvars
mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type
mkInvisForAllTys :: [InvisTVBinder] -> Type -> Type
mkInvisForAllTys [InvisTVBinder]
tyvars Type
ty = (TyCoVarBinder -> Type -> Type) -> Type -> [TyCoVarBinder] -> Type
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr TyCoVarBinder -> Type -> Type
ForAllTy Type
ty ([TyCoVarBinder] -> Type) -> [TyCoVarBinder] -> Type
forall a b. (a -> b) -> a -> b
$ [InvisTVBinder] -> [TyCoVarBinder]
forall a. [VarBndr a Specificity] -> [VarBndr a ArgFlag]
tyVarSpecToBinders [InvisTVBinder]
tyvars
mkPiTy:: TyCoBinder -> Type -> Type
mkPiTy :: TyCoBinder -> Type -> Type
mkPiTy (Anon AnonArgFlag
af Type
ty1) Type
ty2 = FunTy :: AnonArgFlag -> Type -> Type -> Type
FunTy { ft_af :: AnonArgFlag
ft_af = AnonArgFlag
af, ft_arg :: Type
ft_arg = Type
ty1, ft_res :: Type
ft_res = Type
ty2 }
mkPiTy (Named (Bndr TyVar
tv ArgFlag
vis)) Type
ty = TyVar -> ArgFlag -> Type -> Type
mkForAllTy TyVar
tv ArgFlag
vis Type
ty
mkPiTys :: [TyCoBinder] -> Type -> Type
mkPiTys :: [TyCoBinder] -> Type -> Type
mkPiTys [TyCoBinder]
tbs Type
ty = (TyCoBinder -> Type -> Type) -> Type -> [TyCoBinder] -> Type
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
foldr TyCoBinder -> Type -> Type
mkPiTy Type
ty [TyCoBinder]
tbs
mkTyConTy :: TyCon -> Type
mkTyConTy :: TyCon -> Type
mkTyConTy TyCon
tycon = TyCon -> [Type] -> Type
TyConApp TyCon
tycon []
data Coercion
=
Refl Type
| GRefl Role Type MCoercionN
| TyConAppCo Role TyCon [Coercion]
| AppCo Coercion CoercionN
| ForAllCo TyCoVar KindCoercion Coercion
| FunCo Role Coercion Coercion
| CoVarCo CoVar
| AxiomInstCo (CoAxiom Branched) BranchIndex [Coercion]
| AxiomRuleCo CoAxiomRule [Coercion]
| UnivCo UnivCoProvenance Role Type Type
| SymCo Coercion
| TransCo Coercion Coercion
| NthCo Role Int Coercion
| LRCo LeftOrRight CoercionN
| InstCo Coercion CoercionN
| KindCo Coercion
| SubCo CoercionN
| HoleCo CoercionHole
deriving Typeable Coercion
DataType
Constr
Typeable Coercion
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Coercion -> c Coercion)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Coercion)
-> (Coercion -> Constr)
-> (Coercion -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Coercion))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Coercion))
-> ((forall b. Data b => b -> b) -> Coercion -> Coercion)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Coercion -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Coercion -> r)
-> (forall u. (forall d. Data d => d -> u) -> Coercion -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Coercion -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Coercion -> m Coercion)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Coercion -> m Coercion)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Coercion -> m Coercion)
-> Data Coercion
Coercion -> DataType
Coercion -> Constr
(forall b. Data b => b -> b) -> Coercion -> Coercion
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Coercion -> c Coercion
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Coercion
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Coercion -> u
forall u. (forall d. Data d => d -> u) -> Coercion -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Coercion -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Coercion -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Coercion -> m Coercion
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Coercion -> m Coercion
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Coercion
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Coercion -> c Coercion
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Coercion)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Coercion)
$cHoleCo :: Constr
$cSubCo :: Constr
$cKindCo :: Constr
$cInstCo :: Constr
$cLRCo :: Constr
$cNthCo :: Constr
$cTransCo :: Constr
$cSymCo :: Constr
$cUnivCo :: Constr
$cAxiomRuleCo :: Constr
$cAxiomInstCo :: Constr
$cCoVarCo :: Constr
$cFunCo :: Constr
$cForAllCo :: Constr
$cAppCo :: Constr
$cTyConAppCo :: Constr
$cGRefl :: Constr
$cRefl :: Constr
$tCoercion :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Coercion -> m Coercion
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Coercion -> m Coercion
gmapMp :: (forall d. Data d => d -> m d) -> Coercion -> m Coercion
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Coercion -> m Coercion
gmapM :: (forall d. Data d => d -> m d) -> Coercion -> m Coercion
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Coercion -> m Coercion
gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Coercion -> u
gmapQ :: (forall d. Data d => d -> u) -> Coercion -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Coercion -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Coercion -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Coercion -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Coercion -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Coercion -> r
gmapT :: (forall b. Data b => b -> b) -> Coercion -> Coercion
$cgmapT :: (forall b. Data b => b -> b) -> Coercion -> Coercion
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Coercion)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Coercion)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Coercion)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Coercion)
dataTypeOf :: Coercion -> DataType
$cdataTypeOf :: Coercion -> DataType
toConstr :: Coercion -> Constr
$ctoConstr :: Coercion -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Coercion
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Coercion
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Coercion -> c Coercion
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Coercion -> c Coercion
External instance of the constraint type Data Int
External instance of the constraint type Data TyVar
Instance of class: Data of the constraint type Data Coercion
External instance of the constraint type forall a. Data a => Data [a]
Instance of class: Data of the constraint type Data Coercion
External instance of the constraint type Data Role
Instance of class: Data of the constraint type Data Type
External instance of the constraint type Data LeftOrRight
External instance of the constraint type Data CoAxiomRule
External instance of the constraint type forall (br :: BranchFlag). Typeable br => Data (CoAxiom br)
External instance of the constraint type Data Int
External instance of the constraint type Data Int
External instance of the constraint type Data TyVar
Instance of class: Data of the constraint type Data Coercion
External instance of the constraint type forall a. Data a => Data [a]
Instance of class: Data of the constraint type Data Coercion
External instance of the constraint type Data Role
External instance of the constraint type Data Role
Instance of class: Data of the constraint type Data Type
External instance of the constraint type Data TyCon
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type Data TyVar
Instance of class: Data of the constraint type Data CoercionHole
Instance of class: Data of the constraint type Data Type
Instance of class: Data of the constraint type Data MCoercion
Instance of class: Data of the constraint type Data UnivCoProvenance
Instance of class: Data of the constraint type Data Coercion
Data.Data
type CoercionN = Coercion
type CoercionR = Coercion
type CoercionP = Coercion
type KindCoercion = CoercionN
instance Outputable Coercion where
ppr :: Coercion -> SDoc
ppr = Coercion -> SDoc
pprCo
data MCoercion
= MRefl
| MCo Coercion
deriving Typeable MCoercion
DataType
Constr
Typeable MCoercion
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MCoercion -> c MCoercion)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MCoercion)
-> (MCoercion -> Constr)
-> (MCoercion -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MCoercion))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MCoercion))
-> ((forall b. Data b => b -> b) -> MCoercion -> MCoercion)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MCoercion -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MCoercion -> r)
-> (forall u. (forall d. Data d => d -> u) -> MCoercion -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> MCoercion -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MCoercion -> m MCoercion)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MCoercion -> m MCoercion)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MCoercion -> m MCoercion)
-> Data MCoercion
MCoercion -> DataType
MCoercion -> Constr
(forall b. Data b => b -> b) -> MCoercion -> MCoercion
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MCoercion -> c MCoercion
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MCoercion
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> MCoercion -> u
forall u. (forall d. Data d => d -> u) -> MCoercion -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MCoercion -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MCoercion -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MCoercion -> m MCoercion
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MCoercion -> m MCoercion
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MCoercion
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MCoercion -> c MCoercion
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MCoercion)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MCoercion)
$cMCo :: Constr
$cMRefl :: Constr
$tMCoercion :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> MCoercion -> m MCoercion
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MCoercion -> m MCoercion
gmapMp :: (forall d. Data d => d -> m d) -> MCoercion -> m MCoercion
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MCoercion -> m MCoercion
gmapM :: (forall d. Data d => d -> m d) -> MCoercion -> m MCoercion
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MCoercion -> m MCoercion
gmapQi :: Int -> (forall d. Data d => d -> u) -> MCoercion -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MCoercion -> u
gmapQ :: (forall d. Data d => d -> u) -> MCoercion -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MCoercion -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MCoercion -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MCoercion -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MCoercion -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MCoercion -> r
gmapT :: (forall b. Data b => b -> b) -> MCoercion -> MCoercion
$cgmapT :: (forall b. Data b => b -> b) -> MCoercion -> MCoercion
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MCoercion)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MCoercion)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c MCoercion)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MCoercion)
dataTypeOf :: MCoercion -> DataType
$cdataTypeOf :: MCoercion -> DataType
toConstr :: MCoercion -> Constr
$ctoConstr :: MCoercion -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MCoercion
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MCoercion
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MCoercion -> c MCoercion
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MCoercion -> c MCoercion
Instance of class: Data of the constraint type Data Coercion
Data.Data
type MCoercionR = MCoercion
type MCoercionN = MCoercion
instance Outputable MCoercion where
ppr :: MCoercion -> SDoc
ppr MCoercion
MRefl = String -> SDoc
text String
"MRefl"
ppr (MCo Coercion
co) = String -> SDoc
text String
"MCo" SDoc -> SDoc -> SDoc
<+> Coercion -> SDoc
forall a. Outputable a => a -> SDoc
Instance of class: Outputable of the constraint type Outputable Coercion
ppr Coercion
co
data UnivCoProvenance
= PhantomProv KindCoercion
| ProofIrrelProv KindCoercion
| PluginProv String
deriving Typeable UnivCoProvenance
DataType
Constr
Typeable UnivCoProvenance
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UnivCoProvenance -> c UnivCoProvenance)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UnivCoProvenance)
-> (UnivCoProvenance -> Constr)
-> (UnivCoProvenance -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UnivCoProvenance))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UnivCoProvenance))
-> ((forall b. Data b => b -> b)
-> UnivCoProvenance -> UnivCoProvenance)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r)
-> (forall u.
(forall d. Data d => d -> u) -> UnivCoProvenance -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> UnivCoProvenance -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance)
-> Data UnivCoProvenance
UnivCoProvenance -> DataType
UnivCoProvenance -> Constr
(forall b. Data b => b -> b)
-> UnivCoProvenance -> UnivCoProvenance
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UnivCoProvenance -> c UnivCoProvenance
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UnivCoProvenance
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> UnivCoProvenance -> u
forall u. (forall d. Data d => d -> u) -> UnivCoProvenance -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UnivCoProvenance
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UnivCoProvenance -> c UnivCoProvenance
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UnivCoProvenance)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UnivCoProvenance)
$cPluginProv :: Constr
$cProofIrrelProv :: Constr
$cPhantomProv :: Constr
$tUnivCoProvenance :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance
gmapMp :: (forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance
gmapM :: (forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> UnivCoProvenance -> m UnivCoProvenance
gmapQi :: Int -> (forall d. Data d => d -> u) -> UnivCoProvenance -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UnivCoProvenance -> u
gmapQ :: (forall d. Data d => d -> u) -> UnivCoProvenance -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UnivCoProvenance -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UnivCoProvenance -> r
gmapT :: (forall b. Data b => b -> b)
-> UnivCoProvenance -> UnivCoProvenance
$cgmapT :: (forall b. Data b => b -> b)
-> UnivCoProvenance -> UnivCoProvenance
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UnivCoProvenance)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c UnivCoProvenance)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c UnivCoProvenance)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UnivCoProvenance)
dataTypeOf :: UnivCoProvenance -> DataType
$cdataTypeOf :: UnivCoProvenance -> DataType
toConstr :: UnivCoProvenance -> Constr
$ctoConstr :: UnivCoProvenance -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UnivCoProvenance
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UnivCoProvenance
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UnivCoProvenance -> c UnivCoProvenance
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UnivCoProvenance -> c UnivCoProvenance
External instance of the constraint type Data Char
External instance of the constraint type Data Char
Instance of class: Data of the constraint type Data Coercion
External instance of the constraint type Data Char
Instance of class: Data of the constraint type Data Coercion
External instance of the constraint type forall a. Data a => Data [a]
Instance of class: Data of the constraint type Data Coercion
Data.Data
instance Outputable UnivCoProvenance where
ppr :: UnivCoProvenance -> SDoc
ppr (PhantomProv Coercion
_) = String -> SDoc
text String
"(phantom)"
ppr (ProofIrrelProv Coercion
_) = String -> SDoc
text String
"(proof irrel.)"
ppr (PluginProv String
str) = SDoc -> SDoc
parens (String -> SDoc
text String
"plugin" SDoc -> SDoc -> SDoc
<+> SDoc -> SDoc
brackets (String -> SDoc
text String
str))
data CoercionHole
= CoercionHole { CoercionHole -> TyVar
ch_co_var :: CoVar
, CoercionHole -> BlockSubstFlag
ch_blocker :: BlockSubstFlag
, CoercionHole -> IORef (Maybe Coercion)
ch_ref :: IORef (Maybe Coercion)
}
data BlockSubstFlag = YesBlockSubst
| NoBlockSubst
coHoleCoVar :: CoercionHole -> CoVar
coHoleCoVar :: CoercionHole -> TyVar
coHoleCoVar = CoercionHole -> TyVar
ch_co_var
setCoHoleCoVar :: CoercionHole -> CoVar -> CoercionHole
setCoHoleCoVar :: CoercionHole -> TyVar -> CoercionHole
setCoHoleCoVar CoercionHole
h TyVar
cv = CoercionHole
h { ch_co_var :: TyVar
ch_co_var = TyVar
cv }
instance Data.Data CoercionHole where
toConstr :: CoercionHole -> Constr
toConstr CoercionHole
_ = String -> Constr
abstractConstr String
"CoercionHole"
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c CoercionHole
gunfold forall b r. Data b => c (b -> r) -> c r
_ forall r. r -> c r
_ = String -> Constr -> c CoercionHole
forall a. HasCallStack => String -> a
error String
"gunfold"
dataTypeOf :: CoercionHole -> DataType
dataTypeOf CoercionHole
_ = String -> DataType
mkNoRepType String
"CoercionHole"
instance Outputable CoercionHole where
ppr :: CoercionHole -> SDoc
ppr (CoercionHole { ch_co_var :: CoercionHole -> TyVar
ch_co_var = TyVar
cv }) = SDoc -> SDoc
braces (TyVar -> SDoc
forall a. Outputable a => a -> SDoc
External instance of the constraint type Outputable TyVar
ppr TyVar
cv)
instance Outputable BlockSubstFlag where
ppr :: BlockSubstFlag -> SDoc
ppr BlockSubstFlag
YesBlockSubst = String -> SDoc
text String
"YesBlockSubst"
ppr BlockSubstFlag
NoBlockSubst = String -> SDoc
text String
"NoBlockSubst"
data TyCoFolder env a
= TyCoFolder
{ TyCoFolder env a -> Type -> Maybe Type
tcf_view :: Type -> Maybe Type
, TyCoFolder env a -> env -> TyVar -> a
tcf_tyvar :: env -> TyVar -> a
, TyCoFolder env a -> env -> TyVar -> a
tcf_covar :: env -> CoVar -> a
, TyCoFolder env a -> env -> CoercionHole -> a
tcf_hole :: env -> CoercionHole -> a
, TyCoFolder env a -> env -> TyVar -> ArgFlag -> env
tcf_tycobinder :: env -> TyCoVar -> ArgFlag -> env
}
{-# INLINE foldTyCo #-}
foldTyCo :: Monoid a => TyCoFolder env a -> env
-> (Type -> a, [Type] -> a, Coercion -> a, [Coercion] -> a)
foldTyCo :: TyCoFolder env a
-> env -> (Type -> a, [Type] -> a, Coercion -> a, [Coercion] -> a)
foldTyCo (TyCoFolder { tcf_view :: forall env a. TyCoFolder env a -> Type -> Maybe Type
tcf_view = Type -> Maybe Type
view
, tcf_tyvar :: forall env a. TyCoFolder env a -> env -> TyVar -> a
tcf_tyvar = env -> TyVar -> a
tyvar
, tcf_tycobinder :: forall env a. TyCoFolder env a -> env -> TyVar -> ArgFlag -> env
tcf_tycobinder = env -> TyVar -> ArgFlag -> env
tycobinder
, tcf_covar :: forall env a. TyCoFolder env a -> env -> TyVar -> a
tcf_covar = env -> TyVar -> a
covar
, tcf_hole :: forall env a. TyCoFolder env a -> env -> CoercionHole -> a
tcf_hole = env -> CoercionHole -> a
cohole }) env
env
= (env -> Type -> a
go_ty env
env, env -> [Type] -> a
go_tys env
env, env -> Coercion -> a
go_co env
env, env -> [Coercion] -> a
go_cos env
env)
where
go_ty :: env -> Type -> a
go_ty env
env Type
ty | Just Type
ty' <- Type -> Maybe Type
view Type
ty = env -> Type -> a
go_ty env
env Type
ty'
go_ty env
env (TyVarTy TyVar
tv) = env -> TyVar -> a
tyvar env
env TyVar
tv
go_ty env
env (AppTy Type
t1 Type
t2) = env -> Type -> a
go_ty env
env Type
t1 a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Type -> a
go_ty env
env Type
t2
go_ty env
_ (LitTy {}) = a
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid a
mempty
go_ty env
env (CastTy Type
ty Coercion
co) = env -> Type -> a
go_ty env
env Type
ty a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Coercion -> a
go_co env
env Coercion
co
go_ty env
env (CoercionTy Coercion
co) = env -> Coercion -> a
go_co env
env Coercion
co
go_ty env
env (FunTy AnonArgFlag
_ Type
arg Type
res) = env -> Type -> a
go_ty env
env Type
arg a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Type -> a
go_ty env
env Type
res
go_ty env
env (TyConApp TyCon
_ [Type]
tys) = env -> [Type] -> a
go_tys env
env [Type]
tys
go_ty env
env (ForAllTy (Bndr TyVar
tv ArgFlag
vis) Type
inner)
= let !env' :: env
env' = env -> TyVar -> ArgFlag -> env
tycobinder env
env TyVar
tv ArgFlag
vis
in env -> Type -> a
go_ty env
env (TyVar -> Type
varType TyVar
tv) a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Type -> a
go_ty env
env' Type
inner
go_tys :: env -> [Type] -> a
go_tys env
_ [] = a
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid a
mempty
go_tys env
env (Type
t:[Type]
ts) = env -> Type -> a
go_ty env
env Type
t a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> [Type] -> a
go_tys env
env [Type]
ts
go_cos :: env -> [Coercion] -> a
go_cos env
_ [] = a
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid a
mempty
go_cos env
env (Coercion
c:[Coercion]
cs) = env -> Coercion -> a
go_co env
env Coercion
c a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> [Coercion] -> a
go_cos env
env [Coercion]
cs
go_co :: env -> Coercion -> a
go_co env
env (Refl Type
ty) = env -> Type -> a
go_ty env
env Type
ty
go_co env
env (GRefl Role
_ Type
ty MCoercion
MRefl) = env -> Type -> a
go_ty env
env Type
ty
go_co env
env (GRefl Role
_ Type
ty (MCo Coercion
co)) = env -> Type -> a
go_ty env
env Type
ty a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Coercion -> a
go_co env
env Coercion
co
go_co env
env (TyConAppCo Role
_ TyCon
_ [Coercion]
args) = env -> [Coercion] -> a
go_cos env
env [Coercion]
args
go_co env
env (AppCo Coercion
c1 Coercion
c2) = env -> Coercion -> a
go_co env
env Coercion
c1 a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Coercion -> a
go_co env
env Coercion
c2
go_co env
env (FunCo Role
_ Coercion
c1 Coercion
c2) = env -> Coercion -> a
go_co env
env Coercion
c1 a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Coercion -> a
go_co env
env Coercion
c2
go_co env
env (CoVarCo TyVar
cv) = env -> TyVar -> a
covar env
env TyVar
cv
go_co env
env (AxiomInstCo CoAxiom Branched
_ Int
_ [Coercion]
args) = env -> [Coercion] -> a
go_cos env
env [Coercion]
args
go_co env
env (HoleCo CoercionHole
hole) = env -> CoercionHole -> a
cohole env
env CoercionHole
hole
go_co env
env (UnivCo UnivCoProvenance
p Role
_ Type
t1 Type
t2) = env -> UnivCoProvenance -> a
go_prov env
env UnivCoProvenance
p a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Type -> a
go_ty env
env Type
t1
a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Type -> a
go_ty env
env Type
t2
go_co env
env (SymCo Coercion
co) = env -> Coercion -> a
go_co env
env Coercion
co
go_co env
env (TransCo Coercion
c1 Coercion
c2) = env -> Coercion -> a
go_co env
env Coercion
c1 a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Coercion -> a
go_co env
env Coercion
c2
go_co env
env (AxiomRuleCo CoAxiomRule
_ [Coercion]
cos) = env -> [Coercion] -> a
go_cos env
env [Coercion]
cos
go_co env
env (NthCo Role
_ Int
_ Coercion
co) = env -> Coercion -> a
go_co env
env Coercion
co
go_co env
env (LRCo LeftOrRight
_ Coercion
co) = env -> Coercion -> a
go_co env
env Coercion
co
go_co env
env (InstCo Coercion
co Coercion
arg) = env -> Coercion -> a
go_co env
env Coercion
co a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Coercion -> a
go_co env
env Coercion
arg
go_co env
env (KindCo Coercion
co) = env -> Coercion -> a
go_co env
env Coercion
co
go_co env
env (SubCo Coercion
co) = env -> Coercion -> a
go_co env
env Coercion
co
go_co env
env (ForAllCo TyVar
tv Coercion
kind_co Coercion
co)
= env -> Coercion -> a
go_co env
env Coercion
kind_co a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Type -> a
go_ty env
env (TyVar -> Type
varType TyVar
tv)
a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` env -> Coercion -> a
go_co env
env' Coercion
co
where
env' :: env
env' = env -> TyVar -> ArgFlag -> env
tycobinder env
env TyVar
tv ArgFlag
Inferred
go_prov :: env -> UnivCoProvenance -> a
go_prov env
env (PhantomProv Coercion
co) = env -> Coercion -> a
go_co env
env Coercion
co
go_prov env
env (ProofIrrelProv Coercion
co) = env -> Coercion -> a
go_co env
env Coercion
co
go_prov env
_ (PluginProv String
_) = a
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid a
mempty
typeSize :: Type -> Int
typeSize :: Type -> Int
typeSize (LitTy {}) = Int
1
typeSize (TyVarTy {}) = Int
1
typeSize (AppTy Type
t1 Type
t2) = Type -> Int
typeSize Type
t1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Type -> Int
typeSize Type
t2
typeSize (FunTy AnonArgFlag
_ Type
t1 Type
t2) = Type -> Int
typeSize Type
t1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Type -> Int
typeSize Type
t2
typeSize (ForAllTy (Bndr TyVar
tv ArgFlag
_) Type
t) = Type -> Int
typeSize (TyVar -> Type
varType TyVar
tv) Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Type -> Int
typeSize Type
t
typeSize (TyConApp TyCon
_ [Type]
ts) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
External instance of the constraint type Num Int
External instance of the constraint type Foldable []
sum ((Type -> Int) -> [Type] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Type -> Int
typeSize [Type]
ts)
typeSize (CastTy Type
ty Coercion
co) = Type -> Int
typeSize Type
ty Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
typeSize (CoercionTy Coercion
co) = Coercion -> Int
coercionSize Coercion
co
coercionSize :: Coercion -> Int
coercionSize :: Coercion -> Int
coercionSize (Refl Type
ty) = Type -> Int
typeSize Type
ty
coercionSize (GRefl Role
_ Type
ty MCoercion
MRefl) = Type -> Int
typeSize Type
ty
coercionSize (GRefl Role
_ Type
ty (MCo Coercion
co)) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Type -> Int
typeSize Type
ty Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (TyConAppCo Role
_ TyCon
_ [Coercion]
args) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
External instance of the constraint type Num Int
External instance of the constraint type Foldable []
sum ((Coercion -> Int) -> [Coercion] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Coercion -> Int
coercionSize [Coercion]
args)
coercionSize (AppCo Coercion
co Coercion
arg) = Coercion -> Int
coercionSize Coercion
co Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
arg
coercionSize (ForAllCo TyVar
_ Coercion
h Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
h
coercionSize (FunCo Role
_ Coercion
co1 Coercion
co2) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co2
coercionSize (CoVarCo TyVar
_) = Int
1
coercionSize (HoleCo CoercionHole
_) = Int
1
coercionSize (AxiomInstCo CoAxiom Branched
_ Int
_ [Coercion]
args) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
External instance of the constraint type Num Int
External instance of the constraint type Foldable []
sum ((Coercion -> Int) -> [Coercion] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Coercion -> Int
coercionSize [Coercion]
args)
coercionSize (UnivCo UnivCoProvenance
p Role
_ Type
t1 Type
t2) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ UnivCoProvenance -> Int
provSize UnivCoProvenance
p Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Type -> Int
typeSize Type
t1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Type -> Int
typeSize Type
t2
coercionSize (SymCo Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (TransCo Coercion
co1 Coercion
co2) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co2
coercionSize (NthCo Role
_ Int
_ Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (LRCo LeftOrRight
_ Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (InstCo Coercion
co Coercion
arg) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
arg
coercionSize (KindCo Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (SubCo Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (AxiomRuleCo CoAxiomRule
_ [Coercion]
cs) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
External instance of the constraint type Num Int
External instance of the constraint type Foldable []
sum ((Coercion -> Int) -> [Coercion] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Coercion -> Int
coercionSize [Coercion]
cs)
provSize :: UnivCoProvenance -> Int
provSize :: UnivCoProvenance -> Int
provSize (PhantomProv Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
provSize (ProofIrrelProv Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Coercion -> Int
coercionSize Coercion
co
provSize (PluginProv String
_) = Int
1