I'm learning about existential quantification, phantom types, and GADTs at the moment. How do I go about creating a heterogeneous list of a data type with a phantom variable? For example:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ExistentialQuantification #-}
data Toy a where
TBool :: Bool -> Toy Bool
TInt :: Int -> Toy Int
instance Show (Toy a) where
show (TBool b) = "TBool " ++ show b
show (TInt i) = "TInt " ++ show i
bools :: [Toy Bool]
bools = [TBool False, TBool True]
ints :: [Toy Int]
ints = map TInt [0..9]
Having functions like below are OK:
isBool :: Toy a -> Bool
isBool (TBool _) = True
isBool (TInt _) = False
addOne :: Toy Int -> Toy Int
addOne (TInt a) = TInt $ a + 1
However, I would like to be able to declare a heterogeneous list like so:
zeros :: [Toy a]
zeros = [TBool False, TInt 0]
I tried using an empty type class to restrict the type on a
by:
class Unify a
instance Unify Bool
instance Unify Int
zeros :: Unify a => [Toy a]
zeros = [TBool False, TInt 0]
But the above would fail to compile. I was able to use existential quantification to do get the following:
data T = forall a. (Forget a, Show a) => T a
instance Show T where
show (T a) = show a
class (Show a) => Forget a
instance Forget (Toy a)
instance Forget T
zeros :: [T]
zeros = [T (TBool False), T (TInt 0)]
But this way, I cannot apply a function that was based on the specific type of a
in Toy a
to T
e.g. addOne
above.
In conclusion, what are some ways I can create a heterogeneous list without forgetting/losing the phantom variable?
Start with the Toy
type:
data Toy a where
TBool :: Bool -> Toy Bool
TInt :: Int -> Toy Int
Now you can wrap it up in an existential without over-generalizing with the class system:
data WrappedToy where
Wrap :: Toy a -> WrappedToy
Since the wrapper only holds Toy
s, we can unwrap them and get Toy
s back:
incIfInt :: WrappedToy -> WrappedToy
incIfInt (Wrap (TInt n)) = Wrap (TInt (n+1))
incIfInt w = w
And now you can distinguish things within the list:
incIntToys :: [WrappedToy] -> [WrappedToy]
incIntToys = map incIfInt
Edit
As Cirdec points out, the different pieces can be teased apart a bit:
onInt :: (Toy Int -> WrappedToy) -> WrappedToy -> WrappedToy
onInt f (Wrap t@(TInt _)) = f t
onInt _ w = w
mapInt :: (Int -> Int) -> Toy Int -> Toy Int
mapInt f (TInt x) = TInt (f x)
incIntToys :: [WrappedToy] -> [WrappedToy]
incIntToys = map $ onInt (Wrap . mapInt (+1))
I should also note that nothing here so far really justifies the Toy
GADT. bheklilr's simpler approach of using a plain algebraic datatype should work just fine.
There was a very similar question a few days ago.
In your case it would be
{-# LANGUAGE GADTs, PolyKinds, Rank2Types #-}
data Exists :: (k -> *) -> * where
This :: p x -> Exists p
type Toys = [Exists Toy]
zeros :: Toys
zeros = [This (TBool False), This (TInt 0)]
It's easy to eliminate an existential:
recEx :: (forall x. p x -> c) -> Exists p -> c
recEx f (This x) = f x
Then if you have a recursor for the Toy
datatype
recToy :: (Toy Bool -> c) -> (Toy Int -> c) -> Toy a -> c
recToy f g x@(TBool _) = f x
recToy f g x@(TInt _) = g x
you can map a wrapped toy
:
mapToyEx :: (Toy Bool -> p x) -> (Toy Int -> p y) -> Exists Toy -> Exists p
mapToyEx f g = recEx (recToy (This . f) (This . g))
For example
non_zeros :: Toys
non_zeros = map (mapToyEx (const (TBool True)) addOne) zeros
This approach is similar to one in @dfeuer's answer, but it's less ad hoc.
The ordinary heterogeneous list indexed by a list of the types of its elements is
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE GADTs #-}
data HList l where
HNil :: HList '[]
HCons :: a -> HList l -> HList (a ': l)
We can modify this to hold values inside some f :: * -> *
.
data HList1 f l where
HNil1 :: HList1 f '[]
HCons1 :: f a -> HList1 f l -> HList1 f (a ': l)
Which you can use to write zeros
without forgetting the type variables.
zeros :: HList1 Toy [Bool, Int]
zeros = HCons1 (TBool False) $ HCons1 (TInt 0) $ HNil1
Have you played with Data.Typeable
? A Typeable
constraint allows you to make guesses at the type hidden by the existential, and cast to that type when you guess right.
Not your example, but some example code I have lying around:
{-# LANGUAGE GADTs, ScopedTypeVariables, TypeOperators #-}
import Data.Typeable
data Showable where
-- Note that this is an existential defined in GADT form
Showable :: (Typeable a, Show a) => a -> Showable
instance Show Showable where
show (Showable value) = "Showable " ++ show value
-- Example of casting Showable to Integer
castToInteger :: Showable -> Maybe Integer
castToInteger (Showable (value :: a)) =
case eqT :: Maybe (a :~: Integer) of
Just Refl -> Just value
Nothing -> Nothing
example1 = [Showable "foo", Showable 5]
example2 = map castToInteger example1
来源:https://stackoverflow.com/questions/28438040/haskell-heterogeneous-list-for-data-with-phantom-variable