{-# LANGUAGE CPP, DeriveDataTypeable #-}
module DataCon (
        
        DataCon, DataConRep(..),
        SrcStrictness(..), SrcUnpackedness(..),
        HsSrcBang(..), HsImplBang(..),
        StrictnessMark(..),
        ConTag,
        
        EqSpec, mkEqSpec, eqSpecTyVar, eqSpecType,
        eqSpecPair, eqSpecPreds,
        substEqSpec, filterEqSpec,
        
        FieldLbl(..), FieldLabel, FieldLabelString,
        
        mkDataCon, buildAlgTyCon, buildSynTyCon, fIRST_TAG,
        
        dataConRepType, dataConSig, dataConInstSig, dataConFullSig,
        dataConName, dataConIdentity, dataConTag, dataConTagZ,
        dataConTyCon, dataConOrigTyCon,
        dataConUserType,
        dataConUnivTyVars, dataConExTyCoVars, dataConUnivAndExTyCoVars,
        dataConUserTyVars, dataConUserTyVarBinders,
        dataConEqSpec, dataConTheta,
        dataConStupidTheta,
        dataConInstArgTys, dataConOrigArgTys, dataConOrigResTy,
        dataConInstOrigArgTys, dataConRepArgTys,
        dataConFieldLabels, dataConFieldType, dataConFieldType_maybe,
        dataConSrcBangs,
        dataConSourceArity, dataConRepArity,
        dataConIsInfix,
        dataConWorkId, dataConWrapId, dataConWrapId_maybe,
        dataConImplicitTyThings,
        dataConRepStrictness, dataConImplBangs, dataConBoxer,
        splitDataProductType_maybe,
        
        isNullarySrcDataCon, isNullaryRepDataCon, isTupleDataCon, isUnboxedTupleCon,
        isUnboxedSumCon,
        isVanillaDataCon, classDataCon, dataConCannotMatch,
        dataConUserTyVarsArePermuted,
        isBanged, isMarkedStrict, eqHsBang, isSrcStrict, isSrcUnpacked,
        specialPromotedDc,
        
        promoteDataCon
    ) where
#include "HsVersions.h"
import GhcPrelude
import {-# SOURCE #-} MkId( DataConBoxer )
import Type
import ForeignCall ( CType )
import Coercion
import Unify
import TyCon
import FieldLabel
import Class
import Name
import PrelNames
import Var
import VarSet( emptyVarSet )
import Outputable
import Util
import BasicTypes
import FastString
import Module
import Binary
import UniqSet
import Unique( mkAlphaTyVarUnique )
import qualified Data.Data as Data
import Data.Char
import Data.Word
import Data.List( find )
data DataCon
  = MkData {
        DataCon -> Name
dcName    :: Name,      
                                
        DataCon -> Unique
dcUnique :: Unique,     
        DataCon -> ConTag
dcTag    :: ConTag,     
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        DataCon -> Bool
dcVanilla :: Bool,      
                                
                                
                                
                                
                
                
                
                
        
        
        
        
        
        DataCon -> [TyVar]
dcUnivTyVars     :: [TyVar],
        
        
        
        DataCon -> [TyVar]
dcExTyCoVars     :: [TyCoVar],
        
        
        
        
        
        
        
        DataCon -> [TyVarBinder]
dcUserTyVarBinders :: [TyVarBinder],
        DataCon -> [EqSpec]
dcEqSpec :: [EqSpec],   
                                
                                
                                
                                
                
                
                
                
                
                
                
                
                
                
                
                
        DataCon -> ThetaType
dcOtherTheta :: ThetaType,  
                                    
        DataCon -> ThetaType
dcStupidTheta :: ThetaType,     
                                        
                                        
                
                
                
                
                
                
                
                
                
                
                
        DataCon -> ThetaType
dcOrigArgTys :: [Type],         
                                        
        DataCon -> Type
dcOrigResTy :: Type,            
                
                
                
                
        
        DataCon -> [HsSrcBang]
dcSrcBangs :: [HsSrcBang],
                
                
                
                
                
                
        DataCon -> [FieldLabel]
dcFields  :: [FieldLabel],
                
                
                
        
        
        
        DataCon -> TyVar
dcWorkId :: Id,
        
        DataCon -> DataConRep
dcRep      :: DataConRep,
        
        
        
        DataCon -> ConTag
dcRepArity    :: Arity,
        DataCon -> ConTag
dcSourceArity :: Arity,
        
        DataCon -> TyCon
dcRepTyCon  :: TyCon,           
        DataCon -> Type
dcRepType   :: Type,    
                                
                                
                                
                                
        
        
        
        
        
        
        
        
        DataCon -> Bool
dcInfix :: Bool,        
                                
                                
        DataCon -> TyCon
dcPromoted :: TyCon    
                               
  }
data DataConRep
  = 
    NoDataConRep
    
  | DCR { DataConRep -> TyVar
dcr_wrap_id :: Id   
                              
        , DataConRep -> DataConBoxer
dcr_boxer   :: DataConBoxer
        , DataConRep -> ThetaType
dcr_arg_tys :: [Type]  
                                 
                                 
        , DataConRep -> [StrictnessMark]
dcr_stricts :: [StrictnessMark]  
                
        , DataConRep -> [HsImplBang]
dcr_bangs :: [HsImplBang]  
                                     
                                     
    }
data HsSrcBang =
  HsSrcBang SourceText 
            SrcUnpackedness
            SrcStrictness
  deriving Typeable HsSrcBang
DataType
Constr
Typeable HsSrcBang =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c HsSrcBang)
-> (HsSrcBang -> Constr)
-> (HsSrcBang -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c HsSrcBang))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang))
-> ((forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r)
-> (forall u. (forall d. Data d => d -> u) -> HsSrcBang -> [u])
-> (forall u.
    ConTag -> (forall d. Data d => d -> u) -> HsSrcBang -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang)
-> Data HsSrcBang
HsSrcBang -> DataType
HsSrcBang -> Constr
(forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsSrcBang
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. ConTag -> (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. ConTag -> (forall d. Data d => d -> u) -> HsSrcBang -> u
forall u. (forall d. Data d => d -> u) -> HsSrcBang -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsSrcBang
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsSrcBang)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang)
$cHsSrcBang :: Constr
$tHsSrcBang :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang
gmapMp :: (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang
gmapM :: (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang
gmapQi :: ConTag -> (forall d. Data d => d -> u) -> HsSrcBang -> u
$cgmapQi :: forall u. ConTag -> (forall d. Data d => d -> u) -> HsSrcBang -> u
gmapQ :: (forall d. Data d => d -> u) -> HsSrcBang -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HsSrcBang -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r
gmapT :: (forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang
$cgmapT :: (forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c HsSrcBang)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsSrcBang)
dataTypeOf :: HsSrcBang -> DataType
$cdataTypeOf :: HsSrcBang -> DataType
toConstr :: HsSrcBang -> Constr
$ctoConstr :: HsSrcBang -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsSrcBang
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsSrcBang
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang
$cp1Data :: Typeable HsSrcBang
Data.Data
data HsImplBang
  = HsLazy    
  | HsStrict  
  | HsUnpack (Maybe Coercion)
    
    
  deriving Typeable HsImplBang
DataType
Constr
Typeable HsImplBang =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> HsImplBang -> c HsImplBang)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c HsImplBang)
-> (HsImplBang -> Constr)
-> (HsImplBang -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c HsImplBang))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c HsImplBang))
-> ((forall b. Data b => b -> b) -> HsImplBang -> HsImplBang)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r)
-> (forall u. (forall d. Data d => d -> u) -> HsImplBang -> [u])
-> (forall u.
    ConTag -> (forall d. Data d => d -> u) -> HsImplBang -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang)
-> Data HsImplBang
HsImplBang -> DataType
HsImplBang -> Constr
(forall b. Data b => b -> b) -> HsImplBang -> HsImplBang
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsImplBang -> c HsImplBang
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsImplBang
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. ConTag -> (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. ConTag -> (forall d. Data d => d -> u) -> HsImplBang -> u
forall u. (forall d. Data d => d -> u) -> HsImplBang -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsImplBang -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsImplBang -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsImplBang
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsImplBang -> c HsImplBang
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsImplBang)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImplBang)
$cHsUnpack :: Constr
$cHsStrict :: Constr
$cHsLazy :: Constr
$tHsImplBang :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang
gmapMp :: (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang
gmapM :: (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang
gmapQi :: ConTag -> (forall d. Data d => d -> u) -> HsImplBang -> u
$cgmapQi :: forall u. ConTag -> (forall d. Data d => d -> u) -> HsImplBang -> u
gmapQ :: (forall d. Data d => d -> u) -> HsImplBang -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> HsImplBang -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsImplBang -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> HsImplBang -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsImplBang -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> HsImplBang -> r
gmapT :: (forall b. Data b => b -> b) -> HsImplBang -> HsImplBang
$cgmapT :: (forall b. Data b => b -> b) -> HsImplBang -> HsImplBang
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImplBang)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImplBang)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c HsImplBang)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c HsImplBang)
dataTypeOf :: HsImplBang -> DataType
$cdataTypeOf :: HsImplBang -> DataType
toConstr :: HsImplBang -> Constr
$ctoConstr :: HsImplBang -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsImplBang
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HsImplBang
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsImplBang -> c HsImplBang
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> HsImplBang -> c HsImplBang
$cp1Data :: Typeable HsImplBang
Data.Data
data SrcStrictness = SrcLazy 
                   | SrcStrict 
                   | NoSrcStrict 
     deriving (SrcStrictness -> SrcStrictness -> Bool
(SrcStrictness -> SrcStrictness -> Bool)
-> (SrcStrictness -> SrcStrictness -> Bool) -> Eq SrcStrictness
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SrcStrictness -> SrcStrictness -> Bool
$c/= :: SrcStrictness -> SrcStrictness -> Bool
== :: SrcStrictness -> SrcStrictness -> Bool
$c== :: SrcStrictness -> SrcStrictness -> Bool
Eq, Typeable SrcStrictness
DataType
Constr
Typeable SrcStrictness =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> SrcStrictness -> c SrcStrictness)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SrcStrictness)
-> (SrcStrictness -> Constr)
-> (SrcStrictness -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SrcStrictness))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SrcStrictness))
-> ((forall b. Data b => b -> b) -> SrcStrictness -> SrcStrictness)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r)
-> (forall u. (forall d. Data d => d -> u) -> SrcStrictness -> [u])
-> (forall u.
    ConTag -> (forall d. Data d => d -> u) -> SrcStrictness -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness)
-> Data SrcStrictness
SrcStrictness -> DataType
SrcStrictness -> Constr
(forall b. Data b => b -> b) -> SrcStrictness -> SrcStrictness
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcStrictness -> c SrcStrictness
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcStrictness
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. ConTag -> (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.
ConTag -> (forall d. Data d => d -> u) -> SrcStrictness -> u
forall u. (forall d. Data d => d -> u) -> SrcStrictness -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcStrictness
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcStrictness -> c SrcStrictness
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SrcStrictness)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SrcStrictness)
$cNoSrcStrict :: Constr
$cSrcStrict :: Constr
$cSrcLazy :: Constr
$tSrcStrictness :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness
gmapMp :: (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness
gmapM :: (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness
gmapQi :: ConTag -> (forall d. Data d => d -> u) -> SrcStrictness -> u
$cgmapQi :: forall u.
ConTag -> (forall d. Data d => d -> u) -> SrcStrictness -> u
gmapQ :: (forall d. Data d => d -> u) -> SrcStrictness -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SrcStrictness -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r
gmapT :: (forall b. Data b => b -> b) -> SrcStrictness -> SrcStrictness
$cgmapT :: (forall b. Data b => b -> b) -> SrcStrictness -> SrcStrictness
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SrcStrictness)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SrcStrictness)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SrcStrictness)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SrcStrictness)
dataTypeOf :: SrcStrictness -> DataType
$cdataTypeOf :: SrcStrictness -> DataType
toConstr :: SrcStrictness -> Constr
$ctoConstr :: SrcStrictness -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcStrictness
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcStrictness
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcStrictness -> c SrcStrictness
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcStrictness -> c SrcStrictness
$cp1Data :: Typeable SrcStrictness
Data.Data)
data SrcUnpackedness = SrcUnpack 
                     | SrcNoUnpack 
                     | NoSrcUnpack 
     deriving (SrcUnpackedness -> SrcUnpackedness -> Bool
(SrcUnpackedness -> SrcUnpackedness -> Bool)
-> (SrcUnpackedness -> SrcUnpackedness -> Bool)
-> Eq SrcUnpackedness
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SrcUnpackedness -> SrcUnpackedness -> Bool
$c/= :: SrcUnpackedness -> SrcUnpackedness -> Bool
== :: SrcUnpackedness -> SrcUnpackedness -> Bool
$c== :: SrcUnpackedness -> SrcUnpackedness -> Bool
Eq, Typeable SrcUnpackedness
DataType
Constr
Typeable SrcUnpackedness =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c SrcUnpackedness)
-> (SrcUnpackedness -> Constr)
-> (SrcUnpackedness -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c SrcUnpackedness))
-> ((forall b. Data b => b -> b)
    -> SrcUnpackedness -> SrcUnpackedness)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> SrcUnpackedness -> [u])
-> (forall u.
    ConTag -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> SrcUnpackedness -> m SrcUnpackedness)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SrcUnpackedness -> m SrcUnpackedness)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> SrcUnpackedness -> m SrcUnpackedness)
-> Data SrcUnpackedness
SrcUnpackedness -> DataType
SrcUnpackedness -> Constr
(forall b. Data b => b -> b) -> SrcUnpackedness -> SrcUnpackedness
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcUnpackedness
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. ConTag -> (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.
ConTag -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u
forall u. (forall d. Data d => d -> u) -> SrcUnpackedness -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SrcUnpackedness -> m SrcUnpackedness
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SrcUnpackedness -> m SrcUnpackedness
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcUnpackedness
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SrcUnpackedness)
$cNoSrcUnpack :: Constr
$cSrcNoUnpack :: Constr
$cSrcUnpack :: Constr
$tSrcUnpackedness :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> SrcUnpackedness -> m SrcUnpackedness
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SrcUnpackedness -> m SrcUnpackedness
gmapMp :: (forall d. Data d => d -> m d)
-> SrcUnpackedness -> m SrcUnpackedness
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> SrcUnpackedness -> m SrcUnpackedness
gmapM :: (forall d. Data d => d -> m d)
-> SrcUnpackedness -> m SrcUnpackedness
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> SrcUnpackedness -> m SrcUnpackedness
gmapQi :: ConTag -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u
$cgmapQi :: forall u.
ConTag -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u
gmapQ :: (forall d. Data d => d -> u) -> SrcUnpackedness -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SrcUnpackedness -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r
gmapT :: (forall b. Data b => b -> b) -> SrcUnpackedness -> SrcUnpackedness
$cgmapT :: (forall b. Data b => b -> b) -> SrcUnpackedness -> SrcUnpackedness
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SrcUnpackedness)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SrcUnpackedness)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness)
dataTypeOf :: SrcUnpackedness -> DataType
$cdataTypeOf :: SrcUnpackedness -> DataType
toConstr :: SrcUnpackedness -> Constr
$ctoConstr :: SrcUnpackedness -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcUnpackedness
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SrcUnpackedness
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness
$cp1Data :: Typeable SrcUnpackedness
Data.Data)
data StrictnessMark = MarkedStrict | NotMarkedStrict
data EqSpec = EqSpec TyVar
                     Type
mkEqSpec :: TyVar -> Type -> EqSpec
mkEqSpec :: TyVar -> Type -> EqSpec
mkEqSpec tv :: TyVar
tv ty :: Type
ty = TyVar -> Type -> EqSpec
EqSpec TyVar
tv Type
ty
eqSpecTyVar :: EqSpec -> TyVar
eqSpecTyVar :: EqSpec -> TyVar
eqSpecTyVar (EqSpec tv :: TyVar
tv _) = TyVar
tv
eqSpecType :: EqSpec -> Type
eqSpecType :: EqSpec -> Type
eqSpecType (EqSpec _ ty :: Type
ty) = Type
ty
eqSpecPair :: EqSpec -> (TyVar, Type)
eqSpecPair :: EqSpec -> (TyVar, Type)
eqSpecPair (EqSpec tv :: TyVar
tv ty :: Type
ty) = (TyVar
tv, Type
ty)
eqSpecPreds :: [EqSpec] -> ThetaType
eqSpecPreds :: [EqSpec] -> ThetaType
eqSpecPreds spec :: [EqSpec]
spec = [ Type -> Type -> Type
mkPrimEqPred (TyVar -> Type
mkTyVarTy TyVar
tv) Type
ty
                   | EqSpec tv :: TyVar
tv ty :: Type
ty <- [EqSpec]
spec ]
substEqSpec :: TCvSubst -> EqSpec -> EqSpec
substEqSpec :: TCvSubst -> EqSpec -> EqSpec
substEqSpec subst :: TCvSubst
subst (EqSpec tv :: TyVar
tv ty :: Type
ty)
  = TyVar -> Type -> EqSpec
EqSpec TyVar
tv' (HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst Type
ty)
  where
    tv' :: TyVar
tv' = String -> Type -> TyVar
getTyVar "substEqSpec" (TCvSubst -> TyVar -> Type
substTyVar TCvSubst
subst TyVar
tv)
filterEqSpec :: [EqSpec] -> [TyVar] -> [TyVar]
filterEqSpec :: [EqSpec] -> [TyVar] -> [TyVar]
filterEqSpec eq_spec :: [EqSpec]
eq_spec
  = (TyVar -> Bool) -> [TyVar] -> [TyVar]
forall a. (a -> Bool) -> [a] -> [a]
filter TyVar -> Bool
not_in_eq_spec
  where
    not_in_eq_spec :: TyVar -> Bool
not_in_eq_spec var :: TyVar
var = (EqSpec -> Bool) -> [EqSpec] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
not (Bool -> Bool) -> (EqSpec -> Bool) -> EqSpec -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TyVar -> TyVar -> Bool
forall a. Eq a => a -> a -> Bool
== TyVar
var) (TyVar -> Bool) -> (EqSpec -> TyVar) -> EqSpec -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EqSpec -> TyVar
eqSpecTyVar) [EqSpec]
eq_spec
instance Outputable EqSpec where
  ppr :: EqSpec -> SDoc
ppr (EqSpec tv :: TyVar
tv ty :: Type
ty) = (TyVar, Type) -> SDoc
forall a. Outputable a => a -> SDoc
ppr (TyVar
tv, Type
ty)
instance Eq DataCon where
    a :: DataCon
a == :: DataCon -> DataCon -> Bool
== b :: DataCon
b = DataCon -> Unique
forall a. Uniquable a => a -> Unique
getUnique DataCon
a Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
== DataCon -> Unique
forall a. Uniquable a => a -> Unique
getUnique DataCon
b
    a :: DataCon
a /= :: DataCon -> DataCon -> Bool
/= b :: DataCon
b = DataCon -> Unique
forall a. Uniquable a => a -> Unique
getUnique DataCon
a Unique -> Unique -> Bool
forall a. Eq a => a -> a -> Bool
/= DataCon -> Unique
forall a. Uniquable a => a -> Unique
getUnique DataCon
b
instance Uniquable DataCon where
    getUnique :: DataCon -> Unique
getUnique = DataCon -> Unique
dcUnique
instance NamedThing DataCon where
    getName :: DataCon -> Name
getName = DataCon -> Name
dcName
instance Outputable DataCon where
    ppr :: DataCon -> SDoc
ppr con :: DataCon
con = Name -> SDoc
forall a. Outputable a => a -> SDoc
ppr (DataCon -> Name
dataConName DataCon
con)
instance OutputableBndr DataCon where
    pprInfixOcc :: DataCon -> SDoc
pprInfixOcc con :: DataCon
con = Name -> SDoc
forall a. (Outputable a, NamedThing a) => a -> SDoc
pprInfixName (DataCon -> Name
dataConName DataCon
con)
    pprPrefixOcc :: DataCon -> SDoc
pprPrefixOcc con :: DataCon
con = Name -> SDoc
forall a. NamedThing a => a -> SDoc
pprPrefixName (DataCon -> Name
dataConName DataCon
con)
instance Data.Data DataCon where
    
    toConstr :: DataCon -> Constr
toConstr _   = String -> Constr
abstractConstr "DataCon"
    gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataCon
gunfold _ _  = String -> Constr -> c DataCon
forall a. HasCallStack => String -> a
error "gunfold"
    dataTypeOf :: DataCon -> DataType
dataTypeOf _ = String -> DataType
mkNoRepType "DataCon"
instance Outputable HsSrcBang where
    ppr :: HsSrcBang -> SDoc
ppr (HsSrcBang _ prag :: SrcUnpackedness
prag mark :: SrcStrictness
mark) = SrcUnpackedness -> SDoc
forall a. Outputable a => a -> SDoc
ppr SrcUnpackedness
prag SDoc -> SDoc -> SDoc
<+> SrcStrictness -> SDoc
forall a. Outputable a => a -> SDoc
ppr SrcStrictness
mark
instance Outputable HsImplBang where
    ppr :: HsImplBang -> SDoc
ppr HsLazy                  = String -> SDoc
text "Lazy"
    ppr (HsUnpack Nothing)      = String -> SDoc
text "Unpacked"
    ppr (HsUnpack (Just co :: Coercion
co))    = String -> SDoc
text "Unpacked" SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
parens (Coercion -> SDoc
forall a. Outputable a => a -> SDoc
ppr Coercion
co)
    ppr HsStrict                = String -> SDoc
text "StrictNotUnpacked"
instance Outputable SrcStrictness where
    ppr :: SrcStrictness -> SDoc
ppr SrcLazy     = Char -> SDoc
char '~'
    ppr SrcStrict   = Char -> SDoc
char '!'
    ppr NoSrcStrict = SDoc
empty
instance Outputable SrcUnpackedness where
    ppr :: SrcUnpackedness -> SDoc
ppr SrcUnpack   = String -> SDoc
text "{-# UNPACK #-}"
    ppr SrcNoUnpack = String -> SDoc
text "{-# NOUNPACK #-}"
    ppr NoSrcUnpack = SDoc
empty
instance Outputable StrictnessMark where
    ppr :: StrictnessMark -> SDoc
ppr MarkedStrict    = String -> SDoc
text "!"
    ppr NotMarkedStrict = SDoc
empty
instance Binary SrcStrictness where
    put_ :: BinHandle -> SrcStrictness -> IO ()
put_ bh :: BinHandle
bh SrcLazy     = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 0
    put_ bh :: BinHandle
bh SrcStrict   = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 1
    put_ bh :: BinHandle
bh NoSrcStrict = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 2
    get :: BinHandle -> IO SrcStrictness
get bh :: BinHandle
bh =
      do Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
         case Word8
h of
           0 -> SrcStrictness -> IO SrcStrictness
forall (m :: * -> *) a. Monad m => a -> m a
return SrcStrictness
SrcLazy
           1 -> SrcStrictness -> IO SrcStrictness
forall (m :: * -> *) a. Monad m => a -> m a
return SrcStrictness
SrcStrict
           _ -> SrcStrictness -> IO SrcStrictness
forall (m :: * -> *) a. Monad m => a -> m a
return SrcStrictness
NoSrcStrict
instance Binary SrcUnpackedness where
    put_ :: BinHandle -> SrcUnpackedness -> IO ()
put_ bh :: BinHandle
bh SrcNoUnpack = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 0
    put_ bh :: BinHandle
bh SrcUnpack   = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 1
    put_ bh :: BinHandle
bh NoSrcUnpack = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh 2
    get :: BinHandle -> IO SrcUnpackedness
get bh :: BinHandle
bh =
      do Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
         case Word8
h of
           0 -> SrcUnpackedness -> IO SrcUnpackedness
forall (m :: * -> *) a. Monad m => a -> m a
return SrcUnpackedness
SrcNoUnpack
           1 -> SrcUnpackedness -> IO SrcUnpackedness
forall (m :: * -> *) a. Monad m => a -> m a
return SrcUnpackedness
SrcUnpack
           _ -> SrcUnpackedness -> IO SrcUnpackedness
forall (m :: * -> *) a. Monad m => a -> m a
return SrcUnpackedness
NoSrcUnpack
eqHsBang :: HsImplBang -> HsImplBang -> Bool
eqHsBang :: HsImplBang -> HsImplBang -> Bool
eqHsBang HsLazy               HsLazy              = Bool
True
eqHsBang HsStrict             HsStrict            = Bool
True
eqHsBang (HsUnpack Nothing)   (HsUnpack Nothing)  = Bool
True
eqHsBang (HsUnpack (Just c1 :: Coercion
c1)) (HsUnpack (Just c2 :: Coercion
c2))
  = Type -> Type -> Bool
eqType (Coercion -> Type
coercionType Coercion
c1) (Coercion -> Type
coercionType Coercion
c2)
eqHsBang _ _                                       = Bool
False
isBanged :: HsImplBang -> Bool
isBanged :: HsImplBang -> Bool
isBanged (HsUnpack {}) = Bool
True
isBanged (HsStrict {}) = Bool
True
isBanged HsLazy        = Bool
False
isSrcStrict :: SrcStrictness -> Bool
isSrcStrict :: SrcStrictness -> Bool
isSrcStrict SrcStrict = Bool
True
isSrcStrict _ = Bool
False
isSrcUnpacked :: SrcUnpackedness -> Bool
isSrcUnpacked :: SrcUnpackedness -> Bool
isSrcUnpacked SrcUnpack = Bool
True
isSrcUnpacked _ = Bool
False
isMarkedStrict :: StrictnessMark -> Bool
isMarkedStrict :: StrictnessMark -> Bool
isMarkedStrict NotMarkedStrict = Bool
False
isMarkedStrict _               = Bool
True   
mkDataCon :: Name
          -> Bool           
          -> TyConRepName   
          -> [HsSrcBang]    
          -> [FieldLabel]   
                            
          -> [TyVar]        
          -> [TyCoVar]      
          -> [TyVarBinder]  
                            
                            
          -> [EqSpec]       
          -> KnotTied ThetaType 
          -> [KnotTied Type]    
          -> KnotTied Type      
          -> RuntimeRepInfo     
          -> KnotTied TyCon     
          -> ConTag             
          -> ThetaType          
                                
          -> Id                 
          -> DataConRep         
          -> DataCon
  
mkDataCon :: Name
-> Bool
-> Name
-> [HsSrcBang]
-> [FieldLabel]
-> [TyVar]
-> [TyVar]
-> [TyVarBinder]
-> [EqSpec]
-> ThetaType
-> ThetaType
-> Type
-> RuntimeRepInfo
-> TyCon
-> ConTag
-> ThetaType
-> TyVar
-> DataConRep
-> DataCon
mkDataCon name :: Name
name declared_infix :: Bool
declared_infix prom_info :: Name
prom_info
          arg_stricts :: [HsSrcBang]
arg_stricts   
          fields :: [FieldLabel]
fields
          univ_tvs :: [TyVar]
univ_tvs ex_tvs :: [TyVar]
ex_tvs user_tvbs :: [TyVarBinder]
user_tvbs
          eq_spec :: [EqSpec]
eq_spec theta :: ThetaType
theta
          orig_arg_tys :: ThetaType
orig_arg_tys orig_res_ty :: Type
orig_res_ty rep_info :: RuntimeRepInfo
rep_info rep_tycon :: TyCon
rep_tycon tag :: ConTag
tag
          stupid_theta :: ThetaType
stupid_theta work_id :: TyVar
work_id rep :: DataConRep
rep
  = DataCon
con
  where
    is_vanilla :: Bool
is_vanilla = [TyVar] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TyVar]
ex_tvs Bool -> Bool -> Bool
&& [EqSpec] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [EqSpec]
eq_spec Bool -> Bool -> Bool
&& ThetaType -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ThetaType
theta
    con :: DataCon
con = MkData :: Name
-> Unique
-> ConTag
-> Bool
-> [TyVar]
-> [TyVar]
-> [TyVarBinder]
-> [EqSpec]
-> ThetaType
-> ThetaType
-> ThetaType
-> Type
-> [HsSrcBang]
-> [FieldLabel]
-> TyVar
-> DataConRep
-> ConTag
-> ConTag
-> TyCon
-> Type
-> Bool
-> TyCon
-> DataCon
MkData {dcName :: Name
dcName = Name
name, dcUnique :: Unique
dcUnique = Name -> Unique
nameUnique Name
name,
                  dcVanilla :: Bool
dcVanilla = Bool
is_vanilla, dcInfix :: Bool
dcInfix = Bool
declared_infix,
                  dcUnivTyVars :: [TyVar]
dcUnivTyVars = [TyVar]
univ_tvs,
                  dcExTyCoVars :: [TyVar]
dcExTyCoVars = [TyVar]
ex_tvs,
                  dcUserTyVarBinders :: [TyVarBinder]
dcUserTyVarBinders = [TyVarBinder]
user_tvbs,
                  dcEqSpec :: [EqSpec]
dcEqSpec = [EqSpec]
eq_spec,
                  dcOtherTheta :: ThetaType
dcOtherTheta = ThetaType
theta,
                  dcStupidTheta :: ThetaType
dcStupidTheta = ThetaType
stupid_theta,
                  dcOrigArgTys :: ThetaType
dcOrigArgTys = ThetaType
orig_arg_tys, dcOrigResTy :: Type
dcOrigResTy = Type
orig_res_ty,
                  dcRepTyCon :: TyCon
dcRepTyCon = TyCon
rep_tycon,
                  dcSrcBangs :: [HsSrcBang]
dcSrcBangs = [HsSrcBang]
arg_stricts,
                  dcFields :: [FieldLabel]
dcFields = [FieldLabel]
fields, dcTag :: ConTag
dcTag = ConTag
tag, dcRepType :: Type
dcRepType = Type
rep_ty,
                  dcWorkId :: TyVar
dcWorkId = TyVar
work_id,
                  dcRep :: DataConRep
dcRep = DataConRep
rep,
                  dcSourceArity :: ConTag
dcSourceArity = ThetaType -> ConTag
forall (t :: * -> *) a. Foldable t => t a -> ConTag
length ThetaType
orig_arg_tys,
                  dcRepArity :: ConTag
dcRepArity = ThetaType -> ConTag
forall (t :: * -> *) a. Foldable t => t a -> ConTag
length ThetaType
rep_arg_tys ConTag -> ConTag -> ConTag
forall a. Num a => a -> a -> a
+ (TyVar -> Bool) -> [TyVar] -> ConTag
forall a. (a -> Bool) -> [a] -> ConTag
count TyVar -> Bool
isCoVar [TyVar]
ex_tvs,
                  dcPromoted :: TyCon
dcPromoted = TyCon
promoted }
        
        
        
    rep_arg_tys :: ThetaType
rep_arg_tys = DataCon -> ThetaType
dataConRepArgTys DataCon
con
    rep_ty :: Type
rep_ty =
      case DataConRep
rep of
        
        
        NoDataConRep -> DataCon -> Type
dataConUserType DataCon
con
        
        
        DCR{} -> [TyVar] -> Type -> Type
mkInvForAllTys [TyVar]
univ_tvs (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ [TyVar] -> Type -> Type
mkTyCoInvForAllTys [TyVar]
ex_tvs (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
                 ThetaType -> Type -> Type
mkFunTys ThetaType
rep_arg_tys (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
                 TyCon -> ThetaType -> Type
mkTyConApp TyCon
rep_tycon ([TyVar] -> ThetaType
mkTyVarTys [TyVar]
univ_tvs)
      
    prom_tv_bndrs :: [TyConBinder]
prom_tv_bndrs = [ ArgFlag -> TyVar -> TyConBinder
mkNamedTyConBinder ArgFlag
vis TyVar
tv
                    | Bndr tv :: TyVar
tv vis :: ArgFlag
vis <- [TyVarBinder]
user_tvbs ]
    prom_arg_bndrs :: [TyConBinder]
prom_arg_bndrs = [TyConBinder] -> ThetaType -> [TyConBinder]
mkCleanAnonTyConBinders [TyConBinder]
prom_tv_bndrs (ThetaType
theta ThetaType -> ThetaType -> ThetaType
forall a. [a] -> [a] -> [a]
++ ThetaType
orig_arg_tys)
    prom_res_kind :: Type
prom_res_kind  = Type
orig_res_ty
    promoted :: TyCon
promoted       = DataCon
-> Name
-> Name
-> [TyConBinder]
-> Type
-> [Role]
-> RuntimeRepInfo
-> TyCon
mkPromotedDataCon DataCon
con Name
name Name
prom_info
                                       ([TyConBinder]
prom_tv_bndrs [TyConBinder] -> [TyConBinder] -> [TyConBinder]
forall a. [a] -> [a] -> [a]
++ [TyConBinder]
prom_arg_bndrs)
                                       Type
prom_res_kind [Role]
roles RuntimeRepInfo
rep_info
    roles :: [Role]
roles = (TyVar -> Role) -> [TyVar] -> [Role]
forall a b. (a -> b) -> [a] -> [b]
map (\tv :: TyVar
tv -> if TyVar -> Bool
isTyVar TyVar
tv then Role
Nominal else Role
Phantom)
                ([TyVar]
univ_tvs [TyVar] -> [TyVar] -> [TyVar]
forall a. [a] -> [a] -> [a]
++ [TyVar]
ex_tvs)
            [Role] -> [Role] -> [Role]
forall a. [a] -> [a] -> [a]
++ (Type -> Role) -> ThetaType -> [Role]
forall a b. (a -> b) -> [a] -> [b]
map (Role -> Type -> Role
forall a b. a -> b -> a
const Role
Representational) ThetaType
orig_arg_tys
mkCleanAnonTyConBinders :: [TyConBinder] -> [Type] -> [TyConBinder]
mkCleanAnonTyConBinders :: [TyConBinder] -> ThetaType -> [TyConBinder]
mkCleanAnonTyConBinders tc_bndrs :: [TyConBinder]
tc_bndrs tys :: ThetaType
tys
  = [ TyVar -> TyConBinder
mkAnonTyConBinder (Name -> Type -> TyVar
mkTyVar Name
name Type
ty)
    | (name :: Name
name, ty :: Type
ty) <- [Name]
fresh_names [Name] -> ThetaType -> [(Name, Type)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` ThetaType
tys ]
  where
    fresh_names :: [Name]
fresh_names = [Name] -> [Name]
freshNames ((TyVar -> Name) -> [TyVar] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map TyVar -> Name
forall a. NamedThing a => a -> Name
getName ([TyConBinder] -> [TyVar]
forall tv argf. [VarBndr tv argf] -> [tv]
binderVars [TyConBinder]
tc_bndrs))
freshNames :: [Name] -> [Name]
freshNames :: [Name] -> [Name]
freshNames avoids :: [Name]
avoids
  = [ Unique -> OccName -> Name
mkSystemName Unique
uniq OccName
occ
    | ConTag
n <- [0..]
    , let uniq :: Unique
uniq = ConTag -> Unique
mkAlphaTyVarUnique ConTag
n
          occ :: OccName
occ = FastString -> OccName
mkTyVarOccFS (String -> FastString
mkFastString ('x' Char -> String -> String
forall a. a -> [a] -> [a]
: ConTag -> String
forall a. Show a => a -> String
show ConTag
n))
    , Bool -> Bool
not (Unique
uniq Unique -> UniqSet Unique -> Bool
forall a. Uniquable a => a -> UniqSet a -> Bool
`elementOfUniqSet` UniqSet Unique
avoid_uniqs)
    , Bool -> Bool
not (OccName
occ OccName -> OccSet -> Bool
`elemOccSet` OccSet
avoid_occs) ]
  where
    avoid_uniqs :: UniqSet Unique
    avoid_uniqs :: UniqSet Unique
avoid_uniqs = [Unique] -> UniqSet Unique
forall a. Uniquable a => [a] -> UniqSet a
mkUniqSet ((Name -> Unique) -> [Name] -> [Unique]
forall a b. (a -> b) -> [a] -> [b]
map Name -> Unique
forall a. Uniquable a => a -> Unique
getUnique [Name]
avoids)
    avoid_occs :: OccSet
    avoid_occs :: OccSet
avoid_occs = [OccName] -> OccSet
mkOccSet ((Name -> OccName) -> [Name] -> [OccName]
forall a b. (a -> b) -> [a] -> [b]
map Name -> OccName
forall a. NamedThing a => a -> OccName
getOccName [Name]
avoids)
dataConName :: DataCon -> Name
dataConName :: DataCon -> Name
dataConName = DataCon -> Name
dcName
dataConTag :: DataCon -> ConTag
dataConTag :: DataCon -> ConTag
dataConTag  = DataCon -> ConTag
dcTag
dataConTagZ :: DataCon -> ConTagZ
dataConTagZ :: DataCon -> ConTag
dataConTagZ con :: DataCon
con = DataCon -> ConTag
dataConTag DataCon
con ConTag -> ConTag -> ConTag
forall a. Num a => a -> a -> a
- ConTag
fIRST_TAG
dataConTyCon :: DataCon -> TyCon
dataConTyCon :: DataCon -> TyCon
dataConTyCon = DataCon -> TyCon
dcRepTyCon
dataConOrigTyCon :: DataCon -> TyCon
dataConOrigTyCon :: DataCon -> TyCon
dataConOrigTyCon dc :: DataCon
dc
  | Just (tc :: TyCon
tc, _) <- TyCon -> Maybe (TyCon, ThetaType)
tyConFamInst_maybe (DataCon -> TyCon
dcRepTyCon DataCon
dc) = TyCon
tc
  | Bool
otherwise                                          = DataCon -> TyCon
dcRepTyCon DataCon
dc
dataConRepType :: DataCon -> Type
dataConRepType :: DataCon -> Type
dataConRepType = DataCon -> Type
dcRepType
dataConIsInfix :: DataCon -> Bool
dataConIsInfix :: DataCon -> Bool
dataConIsInfix = DataCon -> Bool
dcInfix
dataConUnivTyVars :: DataCon -> [TyVar]
dataConUnivTyVars :: DataCon -> [TyVar]
dataConUnivTyVars (MkData { dcUnivTyVars :: DataCon -> [TyVar]
dcUnivTyVars = [TyVar]
tvbs }) = [TyVar]
tvbs
dataConExTyCoVars :: DataCon -> [TyCoVar]
dataConExTyCoVars :: DataCon -> [TyVar]
dataConExTyCoVars (MkData { dcExTyCoVars :: DataCon -> [TyVar]
dcExTyCoVars = [TyVar]
tvbs }) = [TyVar]
tvbs
dataConUnivAndExTyCoVars :: DataCon -> [TyCoVar]
dataConUnivAndExTyCoVars :: DataCon -> [TyVar]
dataConUnivAndExTyCoVars (MkData { dcUnivTyVars :: DataCon -> [TyVar]
dcUnivTyVars = [TyVar]
univ_tvs, dcExTyCoVars :: DataCon -> [TyVar]
dcExTyCoVars = [TyVar]
ex_tvs })
  = [TyVar]
univ_tvs [TyVar] -> [TyVar] -> [TyVar]
forall a. [a] -> [a] -> [a]
++ [TyVar]
ex_tvs
dataConUserTyVars :: DataCon -> [TyVar]
dataConUserTyVars :: DataCon -> [TyVar]
dataConUserTyVars (MkData { dcUserTyVarBinders :: DataCon -> [TyVarBinder]
dcUserTyVarBinders = [TyVarBinder]
tvbs }) = [TyVarBinder] -> [TyVar]
forall tv argf. [VarBndr tv argf] -> [tv]
binderVars [TyVarBinder]
tvbs
dataConUserTyVarBinders :: DataCon -> [TyVarBinder]
dataConUserTyVarBinders :: DataCon -> [TyVarBinder]
dataConUserTyVarBinders = DataCon -> [TyVarBinder]
dcUserTyVarBinders
dataConEqSpec :: DataCon -> [EqSpec]
dataConEqSpec :: DataCon -> [EqSpec]
dataConEqSpec con :: DataCon
con@(MkData { dcEqSpec :: DataCon -> [EqSpec]
dcEqSpec = [EqSpec]
eq_spec, dcOtherTheta :: DataCon -> ThetaType
dcOtherTheta = ThetaType
theta })
  = DataCon -> [EqSpec]
dataConKindEqSpec DataCon
con
    [EqSpec] -> [EqSpec] -> [EqSpec]
forall a. [a] -> [a] -> [a]
++ [EqSpec]
eq_spec [EqSpec] -> [EqSpec] -> [EqSpec]
forall a. [a] -> [a] -> [a]
++
    [ EqSpec
spec   
    | Just (tc :: TyCon
tc, [_k1 :: Type
_k1, _k2 :: Type
_k2, ty1 :: Type
ty1, ty2 :: Type
ty2]) <- (Type -> Maybe (TyCon, ThetaType))
-> ThetaType -> [Maybe (TyCon, ThetaType)]
forall a b. (a -> b) -> [a] -> [b]
map HasDebugCallStack => Type -> Maybe (TyCon, ThetaType)
Type -> Maybe (TyCon, ThetaType)
splitTyConApp_maybe ThetaType
theta
    , TyCon
tc TyCon -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
heqTyConKey
    , EqSpec
spec <- case (Type -> Maybe TyVar
getTyVar_maybe Type
ty1, Type -> Maybe TyVar
getTyVar_maybe Type
ty2) of
                    (Just tv1 :: TyVar
tv1, _) -> [TyVar -> Type -> EqSpec
mkEqSpec TyVar
tv1 Type
ty2]
                    (_, Just tv2 :: TyVar
tv2) -> [TyVar -> Type -> EqSpec
mkEqSpec TyVar
tv2 Type
ty1]
                    _             -> []
    ] [EqSpec] -> [EqSpec] -> [EqSpec]
forall a. [a] -> [a] -> [a]
++
    [ EqSpec
spec   
    | Just (tc :: TyCon
tc, [_k :: Type
_k, ty1 :: Type
ty1, ty2 :: Type
ty2]) <- (Type -> Maybe (TyCon, ThetaType))
-> ThetaType -> [Maybe (TyCon, ThetaType)]
forall a b. (a -> b) -> [a] -> [b]
map HasDebugCallStack => Type -> Maybe (TyCon, ThetaType)
Type -> Maybe (TyCon, ThetaType)
splitTyConApp_maybe ThetaType
theta
    , TyCon
tc TyCon -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
eqTyConKey
    , EqSpec
spec <- case (Type -> Maybe TyVar
getTyVar_maybe Type
ty1, Type -> Maybe TyVar
getTyVar_maybe Type
ty2) of
                    (Just tv1 :: TyVar
tv1, _) -> [TyVar -> Type -> EqSpec
mkEqSpec TyVar
tv1 Type
ty2]
                    (_, Just tv2 :: TyVar
tv2) -> [TyVar -> Type -> EqSpec
mkEqSpec TyVar
tv2 Type
ty1]
                    _             -> []
    ]
dataConKindEqSpec :: DataCon -> [EqSpec]
dataConKindEqSpec :: DataCon -> [EqSpec]
dataConKindEqSpec (MkData {dcExTyCoVars :: DataCon -> [TyVar]
dcExTyCoVars = [TyVar]
ex_tcvs})
  
  
  
  
  
  
  = [ TyVar -> Type -> EqSpec
EqSpec TyVar
tv Type
ty
    | TyVar
cv <- [TyVar]
ex_tcvs
    , TyVar -> Bool
isCoVar TyVar
cv
    , let (_, _, ty1 :: Type
ty1, ty :: Type
ty, _) = HasDebugCallStack => TyVar -> (Type, Type, Type, Type, Role)
TyVar -> (Type, Type, Type, Type, Role)
coVarKindsTypesRole TyVar
cv
          tv :: TyVar
tv = String -> Type -> TyVar
getTyVar "dataConKindEqSpec" Type
ty1
    ]
dataConTheta :: DataCon -> ThetaType
dataConTheta :: DataCon -> ThetaType
dataConTheta con :: DataCon
con@(MkData { dcEqSpec :: DataCon -> [EqSpec]
dcEqSpec = [EqSpec]
eq_spec, dcOtherTheta :: DataCon -> ThetaType
dcOtherTheta = ThetaType
theta })
  = [EqSpec] -> ThetaType
eqSpecPreds (DataCon -> [EqSpec]
dataConKindEqSpec DataCon
con [EqSpec] -> [EqSpec] -> [EqSpec]
forall a. [a] -> [a] -> [a]
++ [EqSpec]
eq_spec) ThetaType -> ThetaType -> ThetaType
forall a. [a] -> [a] -> [a]
++ ThetaType
theta
dataConWorkId :: DataCon -> Id
dataConWorkId :: DataCon -> TyVar
dataConWorkId dc :: DataCon
dc = DataCon -> TyVar
dcWorkId DataCon
dc
dataConWrapId_maybe :: DataCon -> Maybe Id
dataConWrapId_maybe :: DataCon -> Maybe TyVar
dataConWrapId_maybe dc :: DataCon
dc = case DataCon -> DataConRep
dcRep DataCon
dc of
                           NoDataConRep -> Maybe TyVar
forall a. Maybe a
Nothing
                           DCR { dcr_wrap_id :: DataConRep -> TyVar
dcr_wrap_id = TyVar
wrap_id } -> TyVar -> Maybe TyVar
forall a. a -> Maybe a
Just TyVar
wrap_id
dataConWrapId :: DataCon -> Id
dataConWrapId :: DataCon -> TyVar
dataConWrapId dc :: DataCon
dc = case DataCon -> DataConRep
dcRep DataCon
dc of
                     NoDataConRep-> DataCon -> TyVar
dcWorkId DataCon
dc    
                     DCR { dcr_wrap_id :: DataConRep -> TyVar
dcr_wrap_id = TyVar
wrap_id } -> TyVar
wrap_id
dataConImplicitTyThings :: DataCon -> [TyThing]
dataConImplicitTyThings :: DataCon -> [TyThing]
dataConImplicitTyThings (MkData { dcWorkId :: DataCon -> TyVar
dcWorkId = TyVar
work, dcRep :: DataCon -> DataConRep
dcRep = DataConRep
rep })
  = [TyVar -> TyThing
AnId TyVar
work] [TyThing] -> [TyThing] -> [TyThing]
forall a. [a] -> [a] -> [a]
++ [TyThing]
wrap_ids
  where
    wrap_ids :: [TyThing]
wrap_ids = case DataConRep
rep of
                 NoDataConRep               -> []
                 DCR { dcr_wrap_id :: DataConRep -> TyVar
dcr_wrap_id = TyVar
wrap } -> [TyVar -> TyThing
AnId TyVar
wrap]
dataConFieldLabels :: DataCon -> [FieldLabel]
dataConFieldLabels :: DataCon -> [FieldLabel]
dataConFieldLabels = DataCon -> [FieldLabel]
dcFields
dataConFieldType :: DataCon -> FieldLabelString -> Type
dataConFieldType :: DataCon -> FastString -> Type
dataConFieldType con :: DataCon
con label :: FastString
label = case DataCon -> FastString -> Maybe (FieldLabel, Type)
dataConFieldType_maybe DataCon
con FastString
label of
      Just (_, ty :: Type
ty) -> Type
ty
      Nothing      -> String -> SDoc -> Type
forall a. HasCallStack => String -> SDoc -> a
pprPanic "dataConFieldType" (DataCon -> SDoc
forall a. Outputable a => a -> SDoc
ppr DataCon
con SDoc -> SDoc -> SDoc
<+> FastString -> SDoc
forall a. Outputable a => a -> SDoc
ppr FastString
label)
dataConFieldType_maybe :: DataCon -> FieldLabelString
                       -> Maybe (FieldLabel, Type)
dataConFieldType_maybe :: DataCon -> FastString -> Maybe (FieldLabel, Type)
dataConFieldType_maybe con :: DataCon
con label :: FastString
label
  = ((FieldLabel, Type) -> Bool)
-> [(FieldLabel, Type)] -> Maybe (FieldLabel, Type)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((FastString -> FastString -> Bool
forall a. Eq a => a -> a -> Bool
== FastString
label) (FastString -> Bool)
-> ((FieldLabel, Type) -> FastString) -> (FieldLabel, Type) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldLabel -> FastString
forall a. FieldLbl a -> FastString
flLabel (FieldLabel -> FastString)
-> ((FieldLabel, Type) -> FieldLabel)
-> (FieldLabel, Type)
-> FastString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FieldLabel, Type) -> FieldLabel
forall a b. (a, b) -> a
fst) (DataCon -> [FieldLabel]
dcFields DataCon
con [FieldLabel] -> ThetaType -> [(FieldLabel, Type)]
forall a b. [a] -> [b] -> [(a, b)]
`zip` DataCon -> ThetaType
dcOrigArgTys DataCon
con)
dataConSrcBangs :: DataCon -> [HsSrcBang]
dataConSrcBangs :: DataCon -> [HsSrcBang]
dataConSrcBangs = DataCon -> [HsSrcBang]
dcSrcBangs
dataConSourceArity :: DataCon -> Arity
dataConSourceArity :: DataCon -> ConTag
dataConSourceArity (MkData { dcSourceArity :: DataCon -> ConTag
dcSourceArity = ConTag
arity }) = ConTag
arity
dataConRepArity :: DataCon -> Arity
dataConRepArity :: DataCon -> ConTag
dataConRepArity (MkData { dcRepArity :: DataCon -> ConTag
dcRepArity = ConTag
arity }) = ConTag
arity
isNullarySrcDataCon :: DataCon -> Bool
isNullarySrcDataCon :: DataCon -> Bool
isNullarySrcDataCon dc :: DataCon
dc = DataCon -> ConTag
dataConSourceArity DataCon
dc ConTag -> ConTag -> Bool
forall a. Eq a => a -> a -> Bool
== 0
isNullaryRepDataCon :: DataCon -> Bool
isNullaryRepDataCon :: DataCon -> Bool
isNullaryRepDataCon dc :: DataCon
dc = DataCon -> ConTag
dataConRepArity DataCon
dc ConTag -> ConTag -> Bool
forall a. Eq a => a -> a -> Bool
== 0
dataConRepStrictness :: DataCon -> [StrictnessMark]
dataConRepStrictness :: DataCon -> [StrictnessMark]
dataConRepStrictness dc :: DataCon
dc = case DataCon -> DataConRep
dcRep DataCon
dc of
                            NoDataConRep -> [StrictnessMark
NotMarkedStrict | Type
_ <- DataCon -> ThetaType
dataConRepArgTys DataCon
dc]
                            DCR { dcr_stricts :: DataConRep -> [StrictnessMark]
dcr_stricts = [StrictnessMark]
strs } -> [StrictnessMark]
strs
dataConImplBangs :: DataCon -> [HsImplBang]
dataConImplBangs :: DataCon -> [HsImplBang]
dataConImplBangs dc :: DataCon
dc
  = case DataCon -> DataConRep
dcRep DataCon
dc of
      NoDataConRep              -> ConTag -> HsImplBang -> [HsImplBang]
forall a. ConTag -> a -> [a]
replicate (DataCon -> ConTag
dcSourceArity DataCon
dc) HsImplBang
HsLazy
      DCR { dcr_bangs :: DataConRep -> [HsImplBang]
dcr_bangs = [HsImplBang]
bangs } -> [HsImplBang]
bangs
dataConBoxer :: DataCon -> Maybe DataConBoxer
dataConBoxer :: DataCon -> Maybe DataConBoxer
dataConBoxer (MkData { dcRep :: DataCon -> DataConRep
dcRep = DCR { dcr_boxer :: DataConRep -> DataConBoxer
dcr_boxer = DataConBoxer
boxer } }) = DataConBoxer -> Maybe DataConBoxer
forall a. a -> Maybe a
Just DataConBoxer
boxer
dataConBoxer _ = Maybe DataConBoxer
forall a. Maybe a
Nothing
dataConSig :: DataCon -> ([TyCoVar], ThetaType, [Type], Type)
dataConSig :: DataCon -> ([TyVar], ThetaType, ThetaType, Type)
dataConSig con :: DataCon
con@(MkData {dcOrigArgTys :: DataCon -> ThetaType
dcOrigArgTys = ThetaType
arg_tys, dcOrigResTy :: DataCon -> Type
dcOrigResTy = Type
res_ty})
  = (DataCon -> [TyVar]
dataConUnivAndExTyCoVars DataCon
con, DataCon -> ThetaType
dataConTheta DataCon
con, ThetaType
arg_tys, Type
res_ty)
dataConInstSig
  :: DataCon
  -> [Type]    
  -> ([TyCoVar], ThetaType, [Type])  
                                     
dataConInstSig :: DataCon -> ThetaType -> ([TyVar], ThetaType, ThetaType)
dataConInstSig con :: DataCon
con@(MkData { dcUnivTyVars :: DataCon -> [TyVar]
dcUnivTyVars = [TyVar]
univ_tvs, dcExTyCoVars :: DataCon -> [TyVar]
dcExTyCoVars = [TyVar]
ex_tvs
                           , dcOrigArgTys :: DataCon -> ThetaType
dcOrigArgTys = ThetaType
arg_tys })
               univ_tys :: ThetaType
univ_tys
  = ( [TyVar]
ex_tvs'
    , HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTheta TCvSubst
subst (DataCon -> ThetaType
dataConTheta DataCon
con)
    , HasCallStack => TCvSubst -> ThetaType -> ThetaType
TCvSubst -> ThetaType -> ThetaType
substTys   TCvSubst
subst ThetaType
arg_tys)
  where
    univ_subst :: TCvSubst
univ_subst = [TyVar] -> ThetaType -> TCvSubst
HasDebugCallStack => [TyVar] -> ThetaType -> TCvSubst
zipTvSubst [TyVar]
univ_tvs ThetaType
univ_tys
    (subst :: TCvSubst
subst, ex_tvs' :: [TyVar]
ex_tvs') = HasCallStack => TCvSubst -> [TyVar] -> (TCvSubst, [TyVar])
TCvSubst -> [TyVar] -> (TCvSubst, [TyVar])
Type.substVarBndrs TCvSubst
univ_subst [TyVar]
ex_tvs
dataConFullSig :: DataCon
               -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, [Type], Type)
dataConFullSig :: DataCon -> ([TyVar], [TyVar], [EqSpec], ThetaType, ThetaType, Type)
dataConFullSig (MkData {dcUnivTyVars :: DataCon -> [TyVar]
dcUnivTyVars = [TyVar]
univ_tvs, dcExTyCoVars :: DataCon -> [TyVar]
dcExTyCoVars = [TyVar]
ex_tvs,
                        dcEqSpec :: DataCon -> [EqSpec]
dcEqSpec = [EqSpec]
eq_spec, dcOtherTheta :: DataCon -> ThetaType
dcOtherTheta = ThetaType
theta,
                        dcOrigArgTys :: DataCon -> ThetaType
dcOrigArgTys = ThetaType
arg_tys, dcOrigResTy :: DataCon -> Type
dcOrigResTy = Type
res_ty})
  = ([TyVar]
univ_tvs, [TyVar]
ex_tvs, [EqSpec]
eq_spec, ThetaType
theta, ThetaType
arg_tys, Type
res_ty)
dataConOrigResTy :: DataCon -> Type
dataConOrigResTy :: DataCon -> Type
dataConOrigResTy dc :: DataCon
dc = DataCon -> Type
dcOrigResTy DataCon
dc
dataConStupidTheta :: DataCon -> ThetaType
dataConStupidTheta :: DataCon -> ThetaType
dataConStupidTheta dc :: DataCon
dc = DataCon -> ThetaType
dcStupidTheta DataCon
dc
dataConUserType :: DataCon -> Type
dataConUserType :: DataCon -> Type
dataConUserType (MkData { dcUserTyVarBinders :: DataCon -> [TyVarBinder]
dcUserTyVarBinders = [TyVarBinder]
user_tvbs,
                          dcOtherTheta :: DataCon -> ThetaType
dcOtherTheta = ThetaType
theta, dcOrigArgTys :: DataCon -> ThetaType
dcOrigArgTys = ThetaType
arg_tys,
                          dcOrigResTy :: DataCon -> Type
dcOrigResTy = Type
res_ty })
  = [TyVarBinder] -> Type -> Type
mkForAllTys [TyVarBinder]
user_tvbs (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
    ThetaType -> Type -> Type
mkFunTys ThetaType
theta (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
    ThetaType -> Type -> Type
mkFunTys ThetaType
arg_tys (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$
    Type
res_ty
dataConInstArgTys :: DataCon    
                                
                                
                  -> [Type]     
                  -> [Type]
dataConInstArgTys :: DataCon -> ThetaType -> ThetaType
dataConInstArgTys dc :: DataCon
dc@(MkData {dcUnivTyVars :: DataCon -> [TyVar]
dcUnivTyVars = [TyVar]
univ_tvs,
                              dcExTyCoVars :: DataCon -> [TyVar]
dcExTyCoVars = [TyVar]
ex_tvs}) inst_tys :: ThetaType
inst_tys
 = ASSERT2( univ_tvs `equalLength` inst_tys
          , text "dataConInstArgTys" <+> ppr dc $$ ppr univ_tvs $$ ppr inst_tys)
   ASSERT2( null ex_tvs, ppr dc )
   (Type -> Type) -> ThetaType -> ThetaType
forall a b. (a -> b) -> [a] -> [b]
map (HasCallStack => [TyVar] -> ThetaType -> Type -> Type
[TyVar] -> ThetaType -> Type -> Type
substTyWith [TyVar]
univ_tvs ThetaType
inst_tys) (DataCon -> ThetaType
dataConRepArgTys DataCon
dc)
dataConInstOrigArgTys
        :: DataCon      
        -> [Type]       
                        
        -> [Type]
dataConInstOrigArgTys :: DataCon -> ThetaType -> ThetaType
dataConInstOrigArgTys dc :: DataCon
dc@(MkData {dcOrigArgTys :: DataCon -> ThetaType
dcOrigArgTys = ThetaType
arg_tys,
                                  dcUnivTyVars :: DataCon -> [TyVar]
dcUnivTyVars = [TyVar]
univ_tvs,
                                  dcExTyCoVars :: DataCon -> [TyVar]
dcExTyCoVars = [TyVar]
ex_tvs}) inst_tys :: ThetaType
inst_tys
  = ASSERT2( tyvars `equalLength` inst_tys
           , text "dataConInstOrigArgTys" <+> ppr dc $$ ppr tyvars $$ ppr inst_tys )
    (Type -> Type) -> ThetaType -> ThetaType
forall a b. (a -> b) -> [a] -> [b]
map (HasCallStack => TCvSubst -> Type -> Type
TCvSubst -> Type -> Type
substTy TCvSubst
subst) ThetaType
arg_tys
  where
    tyvars :: [TyVar]
tyvars = [TyVar]
univ_tvs [TyVar] -> [TyVar] -> [TyVar]
forall a. [a] -> [a] -> [a]
++ [TyVar]
ex_tvs
    subst :: TCvSubst
subst  = [TyVar] -> ThetaType -> TCvSubst
HasDebugCallStack => [TyVar] -> ThetaType -> TCvSubst
zipTCvSubst [TyVar]
tyvars ThetaType
inst_tys
dataConOrigArgTys :: DataCon -> [Type]
dataConOrigArgTys :: DataCon -> ThetaType
dataConOrigArgTys dc :: DataCon
dc = DataCon -> ThetaType
dcOrigArgTys DataCon
dc
dataConRepArgTys :: DataCon -> [Type]
dataConRepArgTys :: DataCon -> ThetaType
dataConRepArgTys (MkData { dcRep :: DataCon -> DataConRep
dcRep = DataConRep
rep
                         , dcEqSpec :: DataCon -> [EqSpec]
dcEqSpec = [EqSpec]
eq_spec
                         , dcOtherTheta :: DataCon -> ThetaType
dcOtherTheta = ThetaType
theta
                         , dcOrigArgTys :: DataCon -> ThetaType
dcOrigArgTys = ThetaType
orig_arg_tys })
  = case DataConRep
rep of
      NoDataConRep -> ASSERT( null eq_spec ) theta ++ orig_arg_tys
      DCR { dcr_arg_tys :: DataConRep -> ThetaType
dcr_arg_tys = ThetaType
arg_tys } -> ThetaType
arg_tys
dataConIdentity :: DataCon -> [Word8]
dataConIdentity :: DataCon -> [Word8]
dataConIdentity dc :: DataCon
dc = FastString -> [Word8]
bytesFS (UnitId -> FastString
unitIdFS (Module -> UnitId
moduleUnitId Module
mod)) [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++
                  ConTag -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> ConTag
ord ':') Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
: FastString -> [Word8]
bytesFS (ModuleName -> FastString
moduleNameFS (Module -> ModuleName
moduleName Module
mod)) [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++
                  ConTag -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> ConTag
ord '.') Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
: FastString -> [Word8]
bytesFS (OccName -> FastString
occNameFS (Name -> OccName
nameOccName Name
name))
  where name :: Name
name = DataCon -> Name
dataConName DataCon
dc
        mod :: Module
mod  = ASSERT( isExternalName name ) nameModule name
isTupleDataCon :: DataCon -> Bool
isTupleDataCon :: DataCon -> Bool
isTupleDataCon (MkData {dcRepTyCon :: DataCon -> TyCon
dcRepTyCon = TyCon
tc}) = TyCon -> Bool
isTupleTyCon TyCon
tc
isUnboxedTupleCon :: DataCon -> Bool
isUnboxedTupleCon :: DataCon -> Bool
isUnboxedTupleCon (MkData {dcRepTyCon :: DataCon -> TyCon
dcRepTyCon = TyCon
tc}) = TyCon -> Bool
isUnboxedTupleTyCon TyCon
tc
isUnboxedSumCon :: DataCon -> Bool
isUnboxedSumCon :: DataCon -> Bool
isUnboxedSumCon (MkData {dcRepTyCon :: DataCon -> TyCon
dcRepTyCon = TyCon
tc}) = TyCon -> Bool
isUnboxedSumTyCon TyCon
tc
isVanillaDataCon :: DataCon -> Bool
isVanillaDataCon :: DataCon -> Bool
isVanillaDataCon dc :: DataCon
dc = DataCon -> Bool
dcVanilla DataCon
dc
specialPromotedDc :: DataCon -> Bool
specialPromotedDc :: DataCon -> Bool
specialPromotedDc = TyCon -> Bool
isKindTyCon (TyCon -> Bool) -> (DataCon -> TyCon) -> DataCon -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataCon -> TyCon
dataConTyCon
classDataCon :: Class -> DataCon
classDataCon :: Class -> DataCon
classDataCon clas :: Class
clas = case TyCon -> [DataCon]
tyConDataCons (Class -> TyCon
classTyCon Class
clas) of
                      (dict_constr :: DataCon
dict_constr:no_more :: [DataCon]
no_more) -> ASSERT( null no_more ) dict_constr
                      [] -> String -> DataCon
forall a. String -> a
panic "classDataCon"
dataConCannotMatch :: [Type] -> DataCon -> Bool
dataConCannotMatch :: ThetaType -> DataCon -> Bool
dataConCannotMatch tys :: ThetaType
tys con :: DataCon
con
  | ThetaType -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ThetaType
inst_theta   = Bool
False   
  | (Type -> Bool) -> ThetaType -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Type -> Bool
isTyVarTy ThetaType
tys = Bool
False   
  | Bool
otherwise         = [(Type, Type)] -> Bool
typesCantMatch ((Type -> [(Type, Type)]) -> ThetaType -> [(Type, Type)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Type -> [(Type, Type)]
predEqs ThetaType
inst_theta)
  where
    (_, inst_theta :: ThetaType
inst_theta, _) = DataCon -> ThetaType -> ([TyVar], ThetaType, ThetaType)
dataConInstSig DataCon
con ThetaType
tys
    
    predEqs :: Type -> [(Type, Type)]
predEqs pred :: Type
pred = case Type -> PredTree
classifyPredType Type
pred of
                     EqPred NomEq ty1 :: Type
ty1 ty2 :: Type
ty2       -> [(Type
ty1, Type
ty2)]
                     ClassPred eq :: Class
eq [_, ty1 :: Type
ty1, ty2 :: Type
ty2]
                       | Class
eq Class -> Unique -> Bool
forall a. Uniquable a => a -> Unique -> Bool
`hasKey` Unique
eqTyConKey -> [(Type
ty1, Type
ty2)]
                     _                          -> []
dataConUserTyVarsArePermuted :: DataCon -> Bool
dataConUserTyVarsArePermuted :: DataCon -> Bool
dataConUserTyVarsArePermuted (MkData { dcUnivTyVars :: DataCon -> [TyVar]
dcUnivTyVars = [TyVar]
univ_tvs
                                     , dcExTyCoVars :: DataCon -> [TyVar]
dcExTyCoVars = [TyVar]
ex_tvs, dcEqSpec :: DataCon -> [EqSpec]
dcEqSpec = [EqSpec]
eq_spec
                                     , dcUserTyVarBinders :: DataCon -> [TyVarBinder]
dcUserTyVarBinders = [TyVarBinder]
user_tvbs }) =
  ([EqSpec] -> [TyVar] -> [TyVar]
filterEqSpec [EqSpec]
eq_spec [TyVar]
univ_tvs [TyVar] -> [TyVar] -> [TyVar]
forall a. [a] -> [a] -> [a]
++ [TyVar]
ex_tvs) [TyVar] -> [TyVar] -> Bool
forall a. Eq a => a -> a -> Bool
/= [TyVarBinder] -> [TyVar]
forall tv argf. [VarBndr tv argf] -> [tv]
binderVars [TyVarBinder]
user_tvbs
promoteDataCon :: DataCon -> TyCon
promoteDataCon :: DataCon -> TyCon
promoteDataCon (MkData { dcPromoted :: DataCon -> TyCon
dcPromoted = TyCon
tc }) = TyCon
tc
splitDataProductType_maybe
        :: Type                         
        -> Maybe (TyCon,                
                  [Type],               
                  DataCon,              
                  [Type])               
        
        
        
splitDataProductType_maybe :: Type -> Maybe (TyCon, ThetaType, DataCon, ThetaType)
splitDataProductType_maybe ty :: Type
ty
  | Just (tycon :: TyCon
tycon, ty_args :: ThetaType
ty_args) <- HasDebugCallStack => Type -> Maybe (TyCon, ThetaType)
Type -> Maybe (TyCon, ThetaType)
splitTyConApp_maybe Type
ty
  , Just con :: DataCon
con <- TyCon -> Maybe DataCon
isDataProductTyCon_maybe TyCon
tycon
  = (TyCon, ThetaType, DataCon, ThetaType)
-> Maybe (TyCon, ThetaType, DataCon, ThetaType)
forall a. a -> Maybe a
Just (TyCon
tycon, ThetaType
ty_args, DataCon
con, DataCon -> ThetaType -> ThetaType
dataConInstArgTys DataCon
con ThetaType
ty_args)
  | Bool
otherwise
  = Maybe (TyCon, ThetaType, DataCon, ThetaType)
forall a. Maybe a
Nothing
buildAlgTyCon :: Name
              -> [TyVar]               
              -> [Role]
              -> Maybe CType
              -> ThetaType             
              -> AlgTyConRhs
              -> Bool                  
              -> AlgTyConFlav
              -> TyCon
buildAlgTyCon :: Name
-> [TyVar]
-> [Role]
-> Maybe CType
-> ThetaType
-> AlgTyConRhs
-> Bool
-> AlgTyConFlav
-> TyCon
buildAlgTyCon tc_name :: Name
tc_name ktvs :: [TyVar]
ktvs roles :: [Role]
roles cType :: Maybe CType
cType stupid_theta :: ThetaType
stupid_theta rhs :: AlgTyConRhs
rhs
              gadt_syn :: Bool
gadt_syn parent :: AlgTyConFlav
parent
  = Name
-> [TyConBinder]
-> Type
-> [Role]
-> Maybe CType
-> ThetaType
-> AlgTyConRhs
-> AlgTyConFlav
-> Bool
-> TyCon
mkAlgTyCon Name
tc_name [TyConBinder]
binders Type
liftedTypeKind [Role]
roles Maybe CType
cType ThetaType
stupid_theta
               AlgTyConRhs
rhs AlgTyConFlav
parent Bool
gadt_syn
  where
    binders :: [TyConBinder]
binders = [TyVar] -> TyCoVarSet -> [TyConBinder]
mkTyConBindersPreferAnon [TyVar]
ktvs TyCoVarSet
emptyVarSet
buildSynTyCon :: Name -> [KnotTied TyConBinder] -> Kind   
              -> [Role] -> KnotTied Type -> TyCon
buildSynTyCon :: Name -> [TyConBinder] -> Type -> [Role] -> Type -> TyCon
buildSynTyCon name :: Name
name binders :: [TyConBinder]
binders res_kind :: Type
res_kind roles :: [Role]
roles rhs :: Type
rhs
  = Name
-> [TyConBinder] -> Type -> [Role] -> Type -> Bool -> Bool -> TyCon
mkSynonymTyCon Name
name [TyConBinder]
binders Type
res_kind [Role]
roles Type
rhs Bool
is_tau Bool
is_fam_free
  where
    is_tau :: Bool
is_tau      = Type -> Bool
isTauTy Type
rhs
    is_fam_free :: Bool
is_fam_free = Type -> Bool
isFamFreeTy Type
rhs