{-# Language PatternSynonyms, FlexibleContexts, RoleAnnotations, RankNTypes, MagicHash #-}
module Help where
import GHC.Exts hiding (Ptr)
import Data.Type.Coercion
import Unsafe.Coerce
{- Carter's version
data Ptr a = Ptr Addr#
type role Ptr nominal
castPtr :: Ptr a -> Ptr b
castPtr = unsafeCoerce
ptrCoercible
:: (forall a b. Coercible (Ptr a) (Ptr b) => r)
-> r
ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b)
ptrCoercion = Coercion
-}
data Addr = Addr_ Addr#
newtype Ptr a = Ptr_ Addr
type role Ptr nominal
pattern Ptr :: Addr# -> Ptr a
pattern Ptr a# = Ptr_ (Addr_ a#)
castPtr :: Ptr a -> Ptr b
castPtr (Ptr a) = Ptr a
ptrCoercible
:: (forall a b. Coercible (Ptr a) (Ptr b) => r)
-> r
ptrCoercible r = r
ptrCoercion :: Coercion (Ptr a) (Ptr b)
ptrCoercion = Coercion