base-4.8.1.0: Basic libraries

LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilitynot portable
Safe HaskellNone
LanguageHaskell2010

Data.Type.Coercion

Description

Definition of representational equality (Coercion).

Since: 4.7.0.0

Synopsis

Documentation

data Coercion a b where Source

Representational equality. If Coercion a b is inhabited by some terminating value, then the type a has the same underlying representation as the type b.

To use this equality in practice, pattern-match on the Coercion a b to get out the Coercible a b instance, and then use coerce to apply it.

Since: 4.7.0.0

Constructors

Coercion :: Coercible a b => Coercion a b 

Instances

Category k (Coercion k) Source 

Methods

id :: Coercion k a a Source

(.) :: Coercion k b c -> Coercion k a b -> Coercion k a c Source

TestCoercion k (Coercion k a) Source 

Methods

testCoercion :: Coercion k a b -> Coercion k a c -> Maybe (Coercion k b c) Source

Coercible k a b => Bounded (Coercion k a b) Source 
Coercible k a b => Enum (Coercion k a b) Source 

Methods

succ :: Coercion k a b -> Coercion k a b Source

pred :: Coercion k a b -> Coercion k a b Source

toEnum :: Int -> Coercion k a b Source

fromEnum :: Coercion k a b -> Int Source

enumFrom :: Coercion k a b -> [Coercion k a b] Source

enumFromThen :: Coercion k a b -> Coercion k a b -> [Coercion k a b] Source

enumFromTo :: Coercion k a b -> Coercion k a b -> [Coercion k a b] Source

enumFromThenTo :: Coercion k a b -> Coercion k a b -> Coercion k a b -> [Coercion k a b] Source

Eq (Coercion k a b) Source 

Methods

(==) :: Coercion k a b -> Coercion k a b -> Bool

(/=) :: Coercion k a b -> Coercion k a b -> Bool

(Coercible * a b, Data a, Data b) => Data (Coercion * a b) Source 

Methods

gfoldl :: (forall d e. Data d => c (d -> e) -> d -> c e) -> (forall g. g -> c g) -> Coercion * a b -> c (Coercion * a b) Source

gunfold :: (forall d r. Data d => c (d -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Coercion * a b) Source

toConstr :: Coercion * a b -> Constr Source

dataTypeOf :: Coercion * a b -> DataType Source

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Coercion * a b)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Coercion * a b)) Source

gmapT :: (forall c. Data c => c -> c) -> Coercion * a b -> Coercion * a b Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coercion * a b -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coercion * a b -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Coercion * a b -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Coercion * a b -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coercion * a b -> m (Coercion * a b) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion * a b -> m (Coercion * a b) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coercion * a b -> m (Coercion * a b) Source

Ord (Coercion k a b) Source 

Methods

compare :: Coercion k a b -> Coercion k a b -> Ordering

(<) :: Coercion k a b -> Coercion k a b -> Bool

(<=) :: Coercion k a b -> Coercion k a b -> Bool

(>) :: Coercion k a b -> Coercion k a b -> Bool

(>=) :: Coercion k a b -> Coercion k a b -> Bool

max :: Coercion k a b -> Coercion k a b -> Coercion k a b

min :: Coercion k a b -> Coercion k a b -> Coercion k a b

Coercible k a b => Read (Coercion k a b) Source 
Show (Coercion k a b) Source 

Methods

showsPrec :: Int -> Coercion k a b -> ShowS Source

show :: Coercion k a b -> String Source

showList :: [Coercion k a b] -> ShowS Source

coerceWith :: Coercion a b -> a -> b Source

Type-safe cast, using representational equality

sym :: forall a b. Coercion a b -> Coercion b a Source

Symmetry of representational equality

trans :: Coercion a b -> Coercion b c -> Coercion a c Source

Transitivity of representational equality

repr :: (a :~: b) -> Coercion a b Source

Convert propositional (nominal) equality to representational equality

class TestCoercion f where Source

This class contains types where you can learn the equality of two types from information contained in terms. Typically, only singleton types should inhabit this class.

Methods

testCoercion :: f a -> f b -> Maybe (Coercion a b) Source

Conditionally prove the representational equality of a and b.

Instances

TestCoercion k (Coercion k a) Source 

Methods

testCoercion :: Coercion k a b -> Coercion k a c -> Maybe (Coercion k b c) Source

TestCoercion k ((:~:) k a) Source 

Methods

testCoercion :: (:~:) k a b -> (:~:) k a c -> Maybe (Coercion k b c) Source