{-# LANGUAGE DeriveGeneric       #-}
{-# LANGUAGE TypeOperators       #-}
{-# LANGUAGE TypeFamilies        #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GADTs               #-}
{-# LANGUAGE FlexibleInstances   #-}
{-# LANGUAGE StandaloneDeriving  #-}
{-# LANGUAGE NoImplicitPrelude   #-}
{-# LANGUAGE PolyKinds           #-}
{-# LANGUAGE RankNTypes          #-}
module Data.Type.Coercion
  ( Coercion(..)
  , coerceWith
  , gcoerceWith
  , sym
  , trans
  , repr
  , TestCoercion(..)
  ) where
import qualified Data.Type.Equality as Eq
import Data.Maybe
import GHC.Enum
import GHC.Show
import GHC.Read
import GHC.Base
data Coercion a b where
  Coercion :: Coercible a b => Coercion a b
coerceWith :: Coercion a b -> a -> b
coerceWith :: Coercion a b -> a -> b
coerceWith Coercion x :: a
x = a -> b
forall a b. Coercible a b => a -> b
coerce a
x
gcoerceWith :: Coercion a b -> (Coercible a b => r) -> r
gcoerceWith :: Coercion a b -> (Coercible a b => r) -> r
gcoerceWith Coercion x :: Coercible a b => r
x = r
Coercible a b => r
x
sym :: Coercion a b -> Coercion b a
sym :: Coercion a b -> Coercion b a
sym Coercion = Coercion b a
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
trans :: Coercion a b -> Coercion b c -> Coercion a c
trans :: Coercion a b -> Coercion b c -> Coercion a c
trans Coercion Coercion = Coercion a c
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
repr :: (a Eq.:~: b) -> Coercion a b
repr :: (a :~: b) -> Coercion a b
repr Eq.Refl = Coercion a b
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
deriving instance Eq   (Coercion a b)
deriving instance Show (Coercion a b)
deriving instance Ord  (Coercion a b)
deriving instance Coercible a b => Read (Coercion a b)
instance Coercible a b => Enum (Coercion a b) where
  toEnum :: Int -> Coercion a b
toEnum 0 = Coercion a b
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
  toEnum _ = String -> Coercion a b
forall a. String -> a
errorWithoutStackTrace "Data.Type.Coercion.toEnum: bad argument"
  fromEnum :: Coercion a b -> Int
fromEnum Coercion = 0
deriving instance Coercible a b => Bounded (Coercion a b)
class TestCoercion f where
  
  testCoercion :: f a -> f b -> Maybe (Coercion a b)
instance TestCoercion ((Eq.:~:) a) where
  testCoercion :: (a :~: a) -> (a :~: b) -> Maybe (Coercion a b)
testCoercion Eq.Refl Eq.Refl = Coercion a b -> Maybe (Coercion a b)
forall a. a -> Maybe a
Just Coercion a b
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
instance TestCoercion ((Eq.:~~:) a) where
  testCoercion :: (a :~~: a) -> (a :~~: b) -> Maybe (Coercion a b)
testCoercion Eq.HRefl Eq.HRefl = Coercion a b -> Maybe (Coercion a b)
forall a. a -> Maybe a
Just Coercion a b
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
instance TestCoercion (Coercion a) where
  testCoercion :: Coercion a a -> Coercion a b -> Maybe (Coercion a b)
testCoercion Coercion Coercion = Coercion a b -> Maybe (Coercion a b)
forall a. a -> Maybe a
Just Coercion a b
forall k (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion