ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Core.Coercion.Axiom

Description

Module for coercion axioms, used to represent type family instances and newtypes

Synopsis

Documentation

type Branched = 'Branched Source #

type Unbranched = 'Unbranched Source #

mapAccumBranches :: ([CoAxBranch] -> CoAxBranch -> CoAxBranch) -> Branches br -> Branches br Source #

The [CoAxBranch] passed into the mapping function is a list of all previous branches, reversed

data CoAxiom br Source #

A CoAxiom is a "coercion constructor", i.e. a named equality axiom.

Instances

Instances details
Typeable br => Data (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CoAxiom br -> c (CoAxiom br) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CoAxiom br) Source #

toConstr :: CoAxiom br -> Constr Source #

dataTypeOf :: CoAxiom br -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CoAxiom br)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CoAxiom br)) Source #

gmapT :: (forall b. Data b => b -> b) -> CoAxiom br -> CoAxiom br Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CoAxiom br -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CoAxiom br -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CoAxiom br -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CoAxiom br -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CoAxiom br -> m (CoAxiom br) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CoAxiom br -> m (CoAxiom br) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CoAxiom br -> m (CoAxiom br) Source #

NamedThing (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Uniquable (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getUnique :: CoAxiom br -> Unique Source #

Outputable (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiom br -> SDoc Source #

pprPrec :: Rational -> CoAxiom br -> SDoc Source #

Eq (CoAxiom br) Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

(==) :: CoAxiom br -> CoAxiom br -> Bool #

(/=) :: CoAxiom br -> CoAxiom br -> Bool #

data CoAxBranch Source #

Constructors

CoAxBranch 

Instances

Instances details
Data CoAxBranch Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

toConstr :: CoAxBranch -> Constr Source #

dataTypeOf :: CoAxBranch -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CoAxBranch) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoAxBranch) Source #

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

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

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

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

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

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

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

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

Outputable CoAxBranch Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

data Role Source #

Instances

Instances details
Data Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

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 t => (forall d. Data d => c (t d)) -> Maybe (c Role) Source #

dataCast2 :: Typeable 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 :: forall r r'. (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 #

Binary Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Outputable Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Eq Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

Ord Role Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

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 #

data CoAxiomRule Source #

For now, we work only with nominal equality.

Constructors

CoAxiomRule 

Fields

Instances

Instances details
Data CoAxiomRule Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

toConstr :: CoAxiomRule -> Constr Source #

dataTypeOf :: CoAxiomRule -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CoAxiomRule) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CoAxiomRule) Source #

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

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

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

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

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

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

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

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

Uniquable CoAxiomRule Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Outputable CoAxiomRule Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Eq CoAxiomRule Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

Ord CoAxiomRule Source # 
Instance details

Defined in GHC.Core.Coercion.Axiom

type TypeEqn = Pair Type Source #

A more explicit representation for `t1 ~ t2`.