{-# LANGUAGE CPP #-}
module Hackage.Security.Util.Some (
Some(..)
, DictEq(..)
, SomeEq(..)
, DictShow(..)
, SomeShow(..)
, DictPretty(..)
, SomePretty(..)
, typecheckSome
#if !MIN_VERSION_base(4,7,0)
, tyConSome
#endif
) where
#if MIN_VERSION_base(4,7,0)
import Data.Typeable (Typeable)
#else
import qualified Data.Typeable as Typeable
#endif
import Hackage.Security.Util.TypedEmbedded
import Hackage.Security.Util.Pretty
data Some f = forall a. Some (f a)
#if MIN_VERSION_base(4,7,0)
deriving instance Typeable Some
#else
tyConSome :: Typeable.TyCon
tyConSome = Typeable.mkTyCon3 "hackage-security" "Hackage.Security.Util.Some" "Some"
#endif
data DictEq a where
DictEq :: Eq a => DictEq a
class SomeEq f where
someEq :: DictEq (f a)
instance (Typed f, SomeEq f) => Eq (Some f) where
Some (x :: f a) == Some (y :: f a') =
case unify (typeOf x) (typeOf y) of
Nothing -> False
Just Refl -> case someEq :: DictEq (f a) of DictEq -> x == y
data DictShow a where
DictShow :: Show a => DictShow a
class SomeShow f where
someShow :: DictShow (f a)
instance SomeShow f => Show (Some f) where
show (Some (x :: f a)) =
case someShow :: DictShow (f a) of DictShow -> show x
data DictPretty a where
DictPretty :: Pretty a => DictPretty a
class SomePretty f where
somePretty :: DictPretty (f a)
instance SomePretty f => Pretty (Some f) where
pretty (Some (x :: f a)) =
case somePretty :: DictPretty (f a) of DictPretty -> pretty x
typecheckSome :: Typed f => Some f -> Some (TypeOf f) -> Bool
typecheckSome (Some x) (Some typ) =
case unify (typeOf x) typ of
Just Refl -> True
Nothing -> False