{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE MultiWayIf #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.Core.TyCo.Rep (
Type(..),
TyLit(..),
KindOrType, Kind,
KnotTied,
PredType, ThetaType,
ArgFlag(..), AnonArgFlag(..),
Coercion(..),
UnivCoProvenance(..),
CoercionHole(..), coHoleCoVar, setCoHoleCoVar,
CoercionN, CoercionR, CoercionP, KindCoercion,
MCoercion(..), MCoercionR, MCoercionN,
mkTyConTy_, mkTyVarTy, mkTyVarTys,
mkTyCoVarTy, mkTyCoVarTys,
mkFunTy, mkVisFunTy, mkInvisFunTy, mkVisFunTys,
mkForAllTy, mkForAllTys, mkInvisForAllTys,
mkPiTy, mkPiTys,
mkFunTyMany,
mkScaledFunTy,
mkVisFunTyMany, mkVisFunTysMany,
mkInvisFunTyMany, mkInvisFunTysMany,
nonDetCmpTyLit, cmpTyLit,
TyCoBinder(..), TyCoVarBinder, TyBinder,
binderVar, binderVars, binderType, binderArgFlag,
delBinderVar,
isInvisibleArgFlag, isVisibleArgFlag,
isInvisibleBinder, isVisibleBinder,
isTyBinder, isNamedBinder,
pickLR,
TyCoFolder(..), foldTyCo,
typeSize, coercionSize, provSize,
Scaled(..), scaledMult, scaledThing, mapScaledType, Mult
) where
#include "HsVersions.h"
import GHC.Prelude
import {-# SOURCE #-} GHC.Core.TyCo.Ppr ( pprType, pprCo, pprTyLit )
import GHC.Iface.Type
import GHC.Types.Var
import GHC.Types.Var.Set
import GHC.Core.TyCon
import GHC.Core.Coercion.Axiom
import {-# SOURCE #-} GHC.Builtin.Types ( manyDataConTy )
import GHC.Types.Basic ( LeftOrRight(..), pickLR )
import GHC.Types.Unique ( Uniquable(..) )
import GHC.Utils.Outputable
import GHC.Data.FastString
import GHC.Utils.Misc
import GHC.Utils.Panic
import qualified Data.Data as Data hiding ( TyCon )
import Data.IORef ( IORef )
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_mult :: Mult
, Type -> Type
ft_arg :: Type
, Type -> Type
ft_res :: Type }
| LitTy TyLit
| CastTy
Type
KindCoercion
| CoercionTy
Coercion
deriving Typeable Type
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 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Type -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Type -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Type -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Type -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data.Data
instance Outputable Type where
ppr :: Type -> SDoc
ppr = Type -> SDoc
pprType
data TyLit
= NumTyLit Integer
| StrTyLit FastString
| CharTyLit Char
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
Eq, Typeable TyLit
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 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> TyLit -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TyLit -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> TyLit -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TyLit -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data.Data)
nonDetCmpTyLit :: TyLit -> TyLit -> Ordering
nonDetCmpTyLit :: TyLit -> TyLit -> Ordering
nonDetCmpTyLit = (FastString -> NonDetFastString) -> TyLit -> TyLit -> Ordering
forall r. Ord r => (FastString -> r) -> TyLit -> TyLit -> Ordering
cmpTyLitWith FastString -> NonDetFastString
NonDetFastString
cmpTyLit :: TyLit -> TyLit -> Ordering
cmpTyLit :: TyLit -> TyLit -> Ordering
cmpTyLit = (FastString -> LexicalFastString) -> TyLit -> TyLit -> Ordering
forall r. Ord r => (FastString -> r) -> TyLit -> TyLit -> Ordering
cmpTyLitWith FastString -> LexicalFastString
LexicalFastString
{-# INLINE cmpTyLitWith #-}
cmpTyLitWith :: Ord r => (FastString -> r) -> TyLit -> TyLit -> Ordering
cmpTyLitWith :: forall r. Ord r => (FastString -> r) -> TyLit -> TyLit -> Ordering
cmpTyLitWith FastString -> r
_ (NumTyLit Integer
x) (NumTyLit Integer
y) = Integer -> Integer -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Integer
x Integer
y
cmpTyLitWith FastString -> r
w (StrTyLit FastString
x) (StrTyLit FastString
y) = r -> r -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (FastString -> r
w FastString
x) (FastString -> r
w FastString
y)
cmpTyLitWith FastString -> r
_ (CharTyLit Char
x) (CharTyLit Char
y) = Char -> Char -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Char
x Char
y
cmpTyLitWith FastString -> r
_ TyLit
a TyLit
b = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (TyLit -> Int
tag TyLit
a) (TyLit -> Int
tag TyLit
b)
where
tag :: TyLit -> Int
tag :: TyLit -> Int
tag NumTyLit{} = Int
0
tag StrTyLit{} = Int
1
tag CharTyLit{} = Int
2
instance Outputable TyLit where
ppr :: TyLit -> SDoc
ppr = TyLit -> SDoc
pprTyLit
type KnotTied ty = ty
data TyCoBinder
= Named TyCoVarBinder
| Anon AnonArgFlag (Scaled Type)
deriving Typeable TyCoBinder
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 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TyCoBinder -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> TyCoBinder -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TyCoBinder -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
Data.Data
instance Outputable TyCoBinder where
ppr :: TyCoBinder -> SDoc
ppr (Anon AnonArgFlag
af Scaled Type
ty) = AnonArgFlag -> SDoc
forall a. Outputable a => a -> SDoc
ppr AnonArgFlag
af SDoc -> SDoc -> SDoc
<+> Scaled Type -> SDoc
forall a. Outputable a => a -> SDoc
ppr Scaled Type
ty
ppr (Named (Bndr TyVar
v ArgFlag
Required)) = TyVar -> SDoc
forall a. Outputable a => a -> SDoc
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
ppr TyVar
v
Specificity
InferredSpec -> SDoc -> SDoc
braces (TyVar -> SDoc
forall a. Outputable a => a -> SDoc
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 Scaled Type
_) = Bool
True
isInvisibleBinder (Anon AnonArgFlag
VisArg Scaled 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`, `mkVisFunTyMany`,
`mkInvisFunTyMany`
mkFunTy :: AnonArgFlag -> Mult -> Type -> Type -> Type
mkFunTy :: AnonArgFlag -> Type -> Type -> Type -> Type
mkFunTy AnonArgFlag
af Type
mult Type
arg Type
res = FunTy { ft_af :: AnonArgFlag
ft_af = AnonArgFlag
af
, ft_mult :: Type
ft_mult = Type
mult
, ft_arg :: Type
ft_arg = Type
arg
, ft_res :: Type
ft_res = Type
res }
mkScaledFunTy :: AnonArgFlag -> Scaled Type -> Type -> Type
mkScaledFunTy :: AnonArgFlag -> Scaled Type -> Type -> Type
mkScaledFunTy AnonArgFlag
af (Scaled Type
mult Type
arg) Type
res = AnonArgFlag -> Type -> Type -> Type -> Type
mkFunTy AnonArgFlag
af Type
mult Type
arg Type
res
mkVisFunTy, mkInvisFunTy :: Mult -> Type -> Type -> Type
mkVisFunTy :: Type -> Type -> Type -> Type
mkVisFunTy = AnonArgFlag -> Type -> Type -> Type -> Type
mkFunTy AnonArgFlag
VisArg
mkInvisFunTy :: Type -> Type -> Type -> Type
mkInvisFunTy = AnonArgFlag -> Type -> Type -> Type -> Type
mkFunTy AnonArgFlag
InvisArg
mkFunTyMany :: AnonArgFlag -> Type -> Type -> Type
mkFunTyMany :: AnonArgFlag -> Type -> Type -> Type
mkFunTyMany AnonArgFlag
af = AnonArgFlag -> Type -> Type -> Type -> Type
mkFunTy AnonArgFlag
af Type
manyDataConTy
mkVisFunTyMany :: Type -> Type -> Type
mkVisFunTyMany :: Type -> Type -> Type
mkVisFunTyMany = Type -> Type -> Type -> Type
mkVisFunTy Type
manyDataConTy
mkInvisFunTyMany :: Type -> Type -> Type
mkInvisFunTyMany :: Type -> Type -> Type
mkInvisFunTyMany = Type -> Type -> Type -> Type
mkInvisFunTy Type
manyDataConTy
mkVisFunTys :: [Scaled Type] -> Type -> Type
mkVisFunTys :: [Scaled Type] -> Type -> Type
mkVisFunTys [Scaled Type]
tys Type
ty = (Scaled Type -> Type -> Type) -> Type -> [Scaled Type] -> Type
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (AnonArgFlag -> Scaled Type -> Type -> Type
mkScaledFunTy AnonArgFlag
VisArg) Type
ty [Scaled Type]
tys
mkVisFunTysMany :: [Type] -> Type -> Type
mkVisFunTysMany :: [Type] -> Type -> Type
mkVisFunTysMany [Type]
tys Type
ty = (Type -> Type -> Type) -> Type -> [Type] -> Type
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Type -> Type -> Type
mkVisFunTyMany Type
ty [Type]
tys
mkInvisFunTysMany :: [Type] -> Type -> Type
mkInvisFunTysMany :: [Type] -> Type -> Type
mkInvisFunTysMany [Type]
tys Type
ty = (Type -> Type -> Type) -> Type -> [Type] -> Type
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Type -> Type -> Type
mkInvisFunTyMany 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
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
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 Scaled Type
ty1) Type
ty2 = AnonArgFlag -> Scaled Type -> Type -> Type
mkScaledFunTy AnonArgFlag
af Scaled Type
ty1 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
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 CoercionN 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
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 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> Coercion -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Coercion -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Coercion -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Coercion -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
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
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 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u. Int -> (forall d. Data d => d -> u) -> MCoercion -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MCoercion -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> MCoercion -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MCoercion -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
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
ppr Coercion
co
data UnivCoProvenance
= PhantomProv KindCoercion
| ProofIrrelProv KindCoercion
| PluginProv String
| CorePrepProv
Bool
deriving Typeable UnivCoProvenance
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 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)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
MonadPlus m =>
(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 (m :: * -> *).
Monad m =>
(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 :: forall u.
Int -> (forall d. Data d => d -> u) -> UnivCoProvenance -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> UnivCoProvenance -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> UnivCoProvenance -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UnivCoProvenance -> [u]
gmapQr :: forall r r'.
(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 :: forall r r'.
(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 (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(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 (t :: * -> *) (c :: * -> *).
Typeable t =>
(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 (c :: * -> *).
(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 (c :: * -> *).
(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
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))
ppr (CorePrepProv Bool
_) = String -> SDoc
text String
"(CorePrep)"
data CoercionHole
= CoercionHole { CoercionHole -> TyVar
ch_co_var :: CoVar
, CoercionHole -> IORef (Maybe Coercion)
ch_ref :: IORef (Maybe Coercion)
}
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 (c :: * -> *).
(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
ppr TyVar
cv)
instance Uniquable CoercionHole where
getUnique :: CoercionHole -> Unique
getUnique (CoercionHole { ch_co_var :: CoercionHole -> TyVar
ch_co_var = TyVar
cv }) = TyVar -> Unique
forall a. Uniquable a => a -> Unique
getUnique TyVar
cv
data TyCoFolder env a
= TyCoFolder
{ forall env a. TyCoFolder env a -> Type -> Maybe Type
tcf_view :: Type -> Maybe Type
, forall env a. TyCoFolder env a -> env -> TyVar -> a
tcf_tyvar :: env -> TyVar -> a
, forall env a. TyCoFolder env a -> env -> TyVar -> a
tcf_covar :: env -> CoVar -> a
, forall env a. TyCoFolder env a -> env -> CoercionHole -> a
tcf_hole :: env -> CoercionHole -> a
, forall env 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 :: forall a env.
Monoid a =>
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
`mappend` env -> Type -> a
go_ty env
env Type
t2
go_ty env
_ (LitTy {}) = a
forall a. Monoid a => 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
`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
w Type
arg Type
res) = env -> Type -> a
go_ty env
env Type
w a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` env -> Type -> a
go_ty env
env Type
arg a -> a -> a
forall a. Monoid a => a -> a -> 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
`mappend` env -> Type -> a
go_ty env
env' Type
inner
go_tys :: env -> [Type] -> a
go_tys env
_ [] = a
forall a. Monoid a => 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
`mappend` env -> [Type] -> a
go_tys env
env [Type]
ts
go_cos :: env -> [Coercion] -> a
go_cos env
_ [] = a
forall a. Monoid a => 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
`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
`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
`mappend` env -> Coercion -> a
go_co env
env Coercion
c2
go_co env
env (FunCo Role
_ Coercion
cw Coercion
c1 Coercion
c2) = env -> Coercion -> a
go_co env
env Coercion
cw a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend`
env -> Coercion -> a
go_co env
env Coercion
c1 a -> a -> a
forall a. Monoid a => a -> a -> 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
`mappend` env -> Type -> a
go_ty env
env Type
t1
a -> a -> a
forall a. Monoid a => a -> a -> 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
`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
`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
`mappend` env -> Type -> a
go_ty env
env (TyVar -> Type
varType TyVar
tv)
a -> a -> a
forall a. Monoid a => a -> a -> 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
mempty
go_prov env
_ (CorePrepProv Bool
_) = a
forall a. Monoid a => 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
+ Type -> Int
typeSize Type
t2
typeSize (FunTy AnonArgFlag
_ Type
_ Type
t1 Type
t2) = Type -> Int
typeSize Type
t1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 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
+ Type -> Int
typeSize Type
t
typeSize (TyConApp TyCon
_ [Type]
ts) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
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
+ 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
+ Type -> Int
typeSize Type
ty Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (TyConAppCo Role
_ TyCon
_ [Coercion]
args) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
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
+ Coercion -> Int
coercionSize Coercion
arg
coercionSize (ForAllCo TyVar
_ Coercion
h Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
h
coercionSize (FunCo Role
_ Coercion
w Coercion
co1 Coercion
co2) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co2
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
w
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
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
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
+ UnivCoProvenance -> Int
provSize UnivCoProvenance
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Type -> Int
typeSize Type
t1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Type -> Int
typeSize Type
t2
coercionSize (SymCo Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (TransCo Coercion
co1 Coercion
co2) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co2
coercionSize (NthCo Role
_ Int
_ Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (LRCo LeftOrRight
_ Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (InstCo Coercion
co Coercion
arg) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
arg
coercionSize (KindCo Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (SubCo Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co
coercionSize (AxiomRuleCo CoAxiomRule
_ [Coercion]
cs) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
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
+ Coercion -> Int
coercionSize Coercion
co
provSize (ProofIrrelProv Coercion
co) = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Coercion -> Int
coercionSize Coercion
co
provSize (PluginProv String
_) = Int
1
provSize (CorePrepProv Bool
_) = Int
1
data Scaled a = Scaled !Mult a
deriving (Typeable (Scaled a)
Typeable (Scaled a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scaled a -> c (Scaled a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Scaled a))
-> (Scaled a -> Constr)
-> (Scaled a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Scaled a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Scaled a)))
-> ((forall b. Data b => b -> b) -> Scaled a -> Scaled a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Scaled a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Scaled a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a))
-> Data (Scaled a)
Scaled a -> DataType
Scaled a -> Constr
(forall b. Data b => b -> b) -> Scaled a -> Scaled a
forall {a}. Data a => Typeable (Scaled a)
forall a. Data a => Scaled a -> DataType
forall a. Data a => Scaled a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> Scaled a -> Scaled a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Scaled a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> Scaled a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Scaled a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scaled a -> c (Scaled a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Scaled a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Scaled a))
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) -> Scaled a -> u
forall u. (forall d. Data d => d -> u) -> Scaled a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Scaled a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scaled a -> c (Scaled a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Scaled a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Scaled a))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Scaled a -> m (Scaled a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Scaled a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Scaled a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Scaled a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> Scaled a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Scaled a -> r
gmapT :: (forall b. Data b => b -> b) -> Scaled a -> Scaled a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Scaled a -> Scaled a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Scaled a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Scaled a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Scaled a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Scaled a))
dataTypeOf :: Scaled a -> DataType
$cdataTypeOf :: forall a. Data a => Scaled a -> DataType
toConstr :: Scaled a -> Constr
$ctoConstr :: forall a. Data a => Scaled a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Scaled a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Scaled a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scaled a -> c (Scaled a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Scaled a -> c (Scaled a)
Data.Data)
instance (Outputable a) => Outputable (Scaled a) where
ppr :: Scaled a -> SDoc
ppr (Scaled Type
_cnt a
t) = a -> SDoc
forall a. Outputable a => a -> SDoc
ppr a
t
scaledMult :: Scaled a -> Mult
scaledMult :: forall a. Scaled a -> Type
scaledMult (Scaled Type
m a
_) = Type
m
scaledThing :: Scaled a -> a
scaledThing :: forall a. Scaled a -> a
scaledThing (Scaled Type
_ a
t) = a
t
mapScaledType :: (Type -> Type) -> Scaled Type -> Scaled Type
mapScaledType :: (Type -> Type) -> Scaled Type -> Scaled Type
mapScaledType Type -> Type
f (Scaled Type
m Type
t) = Type -> Type -> Scaled Type
forall a. Type -> a -> Scaled a
Scaled (Type -> Type
f Type
m) (Type -> Type
f Type
t)
type Mult = Type