{-# LANGUAGE RankNTypes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleInstances #-} module Data.Type.Internal.Helpers where import Data.Type.Kind import Data.Type.Internal.Framework import Data.Type.Internal.Body import Unsafe.Coerce (unsafeCoerce) typeOf :: forall t. t -> Type t typeOf _ = Type cast :: forall f t. (Meta f, Meta t) => f -> Maybe t cast x = if typeID (Type :: Type f) == typeID (Type :: Type t) then Just $ unsafeCoerce x else Nothing coerce :: forall f t. (Meta f, Meta t) => f -> t coerce x = case cast x of Just x -> x Nothing -> error "Data.Type.coerce failed!"