ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

TcEvidence

Synopsis

Documentation

data HsWrapper Source

Instances

Data HsWrapper 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsWrapper -> c HsWrapper Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsWrapper Source

toConstr :: HsWrapper -> Constr Source

dataTypeOf :: HsWrapper -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c HsWrapper) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsWrapper) Source

gmapT :: (forall b. Data b => b -> b) -> HsWrapper -> HsWrapper Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsWrapper -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsWrapper -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsWrapper -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsWrapper -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsWrapper -> m HsWrapper Source

Outputable HsWrapper 

mkWpFuns :: [(TcType, HsWrapper)] -> TcType -> HsWrapper -> HsWrapper Source

mkWpFuns [(ty1, wrap1), (ty2, wrap2)] ty_res wrap_res, where wrap1 :: ty1 "->" ty1' and wrap2 :: ty2 "->" ty2', wrap3 :: ty3 "->" ty3' and ty_res is either ty3 or ty3', gives a wrapper (ty1' -> ty2' -> ty3) "->" (ty1 -> ty2 -> ty3'). Notice that the result wrapper goes the other way round to all the others. This is a result of sub-typing contravariance.

data TcEvBinds Source

Instances

Data TcEvBinds 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TcEvBinds -> c TcEvBinds Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TcEvBinds Source

toConstr :: TcEvBinds -> Constr Source

dataTypeOf :: TcEvBinds -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c TcEvBinds) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TcEvBinds) Source

gmapT :: (forall b. Data b => b -> b) -> TcEvBinds -> TcEvBinds Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TcEvBinds -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TcEvBinds -> r Source

gmapQ :: (forall d. Data d => d -> u) -> TcEvBinds -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> TcEvBinds -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TcEvBinds -> m TcEvBinds Source

Outputable TcEvBinds 

newtype EvBindMap Source

Constructors

EvBindMap 

foldEvBindMap :: (EvBind -> a -> a) -> a -> EvBindMap -> a Source

data EvBind Source

Constructors

EvBind 

sccEvBinds :: Bag EvBind -> [SCC EvBind] Source

Do SCC analysis on a bag of EvBinds.

data EvTerm Source

Instances

Data EvTerm 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvTerm -> c EvTerm Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvTerm Source

toConstr :: EvTerm -> Constr Source

dataTypeOf :: EvTerm -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c EvTerm) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTerm) Source

gmapT :: (forall b. Data b => b -> b) -> EvTerm -> EvTerm Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTerm -> r Source

gmapQ :: (forall d. Data d => d -> u) -> EvTerm -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvTerm -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTerm -> m EvTerm Source

Outputable EvTerm 

data EvLit Source

Constructors

EvNum Integer 
EvStr FastString 

Instances

Data EvLit 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvLit -> c EvLit Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvLit Source

toConstr :: EvLit -> Constr Source

dataTypeOf :: EvLit -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c EvLit) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvLit) Source

gmapT :: (forall b. Data b => b -> b) -> EvLit -> EvLit Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvLit -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvLit -> r Source

gmapQ :: (forall d. Data d => d -> u) -> EvLit -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvLit -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvLit -> m EvLit Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvLit -> m EvLit Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvLit -> m EvLit Source

Outputable EvLit 

data EvCallStack Source

Evidence for CallStack implicit parameters.

Constructors

EvCsEmpty 
EvCsPushCall Name RealSrcSpan EvTerm

EvCsPushCall name loc stk represents a call to name, occurring at loc, in a calling context stk.

Instances

Data EvCallStack 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvCallStack -> c EvCallStack Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvCallStack Source

toConstr :: EvCallStack -> Constr Source

dataTypeOf :: EvCallStack -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c EvCallStack) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvCallStack) Source

gmapT :: (forall b. Data b => b -> b) -> EvCallStack -> EvCallStack Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvCallStack -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvCallStack -> r Source

gmapQ :: (forall d. Data d => d -> u) -> EvCallStack -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvCallStack -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvCallStack -> m EvCallStack Source

Outputable EvCallStack 

data EvTypeable Source

Instructions on how to make a Typeable dictionary. See Note [Typeable evidence terms]

Constructors

EvTypeableTyCon [EvTerm]

Dictionary for Typeable (T k1..kn). The EvTerms are for the arguments

EvTypeableTyApp EvTerm EvTerm

Dictionary for Typeable (s t), given a dictionaries for s and t

EvTypeableTyLit EvTerm

Dictionary for a type literal, e.g. Typeable "foo" or Typeable 3 The EvTerm is evidence of, e.g., KnownNat 3 (see Trac #10348)

Instances

Data EvTypeable 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvTypeable -> c EvTypeable Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvTypeable Source

toConstr :: EvTypeable -> Constr Source

dataTypeOf :: EvTypeable -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c EvTypeable) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvTypeable) Source

gmapT :: (forall b. Data b => b -> b) -> EvTypeable -> EvTypeable Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvTypeable -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvTypeable -> r Source

gmapQ :: (forall d. Data d => d -> u) -> EvTypeable -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvTypeable -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvTypeable -> m EvTypeable Source

Outputable EvTypeable 

data CoercionHole Source

A coercion to be filled in by the type-checker. See Note [Coercion holes]

Instances

Data CoercionHole 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoercionHole -> c CoercionHole Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CoercionHole Source

toConstr :: CoercionHole -> Constr Source

dataTypeOf :: CoercionHole -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c CoercionHole) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoercionHole) Source

gmapT :: (forall b. Data b => b -> b) -> CoercionHole -> CoercionHole Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoercionHole -> r Source

gmapQ :: (forall d. Data d => d -> u) -> CoercionHole -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> CoercionHole -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoercionHole -> m CoercionHole Source

Outputable CoercionHole 

data Role Source

Instances

Eq Role 

Methods

(==) :: Role -> Role -> Bool

(/=) :: Role -> Role -> Bool

Data Role 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role Source

toConstr :: Role -> Constr Source

dataTypeOf :: Role -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c Role) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) Source

gmapT :: (forall b. Data b => b -> b) -> Role -> Role Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role Source

Ord Role 

Methods

compare :: Role -> Role -> Ordering

(<) :: Role -> Role -> Bool

(<=) :: Role -> Role -> Bool

(>) :: Role -> Role -> Bool

(>=) :: Role -> Role -> Bool

max :: Role -> Role -> Role

min :: Role -> Role -> Role

Outputable Role 
Binary Role 

data LeftOrRight Source

Constructors

CLeft 
CRight 

Instances

Eq LeftOrRight 
Data LeftOrRight 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight Source

toConstr :: LeftOrRight -> Constr Source

dataTypeOf :: LeftOrRight -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) Source

gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r Source

gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source

Outputable LeftOrRight 
Binary LeftOrRight 

pickLR :: LeftOrRight -> (a, a) -> a Source

unwrapIP :: Type -> CoercionR Source

Create a Coercion that unwraps an implicit-parameter or overloaded-label dictionary to expose the underlying value. We expect the Type to have the form `IP sym ty` or `IsLabel sym ty`, and return a Coercion `co :: IP sym ty ~ ty` or `co :: IsLabel sym ty ~ Proxy# sym -> ty`. See also Note [Type-checking overloaded labels] in TcExpr.

wrapIP :: Type -> CoercionR Source

Create a Coercion that wraps a value in an implicit-parameter dictionary. See unwrapIP.