10

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?

gspindles
  • 187
  • 6
  • 7
    Maybe you toy example is a little too simplified from your actual use case, but wouldn't this be easily solvable with a simple ADT instead of a GADT? `data Toy = TBool Bool | TInt Int`; `isBool (TBool _) = True; isBool _ = False`, `addOne (TInt a) = TInt $ a + 1`; `zeros = [Toy]; zeros = [TBool False, TInt 0]`. Or do you really need that polymorphism there and your actual use case is more complex? – bheklilr Feb 10 '15 at 17:40
  • @bheklilr I have some composite data, say `data Sequence = Sequence (Toy Int)` where it doesnot apply to `Toy Bool`, and vice versa. And also, in your reply, wouldn't your definition of `addOne` not total? .i.e. Calling `addOne` on `TBool b` would cause an error? – gspindles Feb 10 '15 at 18:02
  • 1
    Sorry, meant to have `addOne (TInt a) = TInt $ a + 1; addOne x = x`. – bheklilr Feb 10 '15 at 18:07
  • @gspindles can't you have `newtype TInt = TInt Int`, `TBool` similarly and `data Toy = ToyInt TInt | ToyBool TBool`. So you can have `Sequence TInt`. I wouldn't use GADTs before they are really necessary, e.g. having constructor like `EqToy :: Toy a -> Toy a -> Toy Bool` or `MultiToy :: Toy a -> Toy [a]` – phadej Feb 11 '15 at 05:48
  • @phagej That was actually my original implementation (except I didn't think to use `newtype` instead of `data`). But untimately, I wanted to work with `Toy` as the bottom most data where everything else operarates on. Hence the need for the phantom and going out of my way to make it work in higher up composite data/function. I.e. in the `Sequence` data in reply to @bleklilr, I don't want `Sequence` to take `TInt` in your example, I want it to take a `Toy`. – gspindles Feb 11 '15 at 06:36

4 Answers4

10

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 Toys, we can unwrap them and get Toys 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.

dfeuer
  • 48,079
  • 5
  • 63
  • 167
  • 1
    For practical use, this answer can be improved by splitting out the unwrapping by type from incrementing. `onInt :: (Toy Int -> WrappedToy) -> WrappedToy -> WrappedToy; onInt f (Wrap t@(TInt _)) = f t; onInt _ w = w`. Then, with a suitable `mapInt f (TInt x) = TInt (f x)` the example `incIfInt` can be written as `onInt (Wrap . mapInt (+1))`. – Cirdec Feb 10 '15 at 18:14
  • @Cirdec, that does sound sensible. – dfeuer Feb 10 '15 at 18:21
  • 2
    The knowledge that what is held in a `WrappedToy` is a `Toy` isn't accomplishing anything. It can be written more generically as `data Wrapped f where Wrap :: f a -> Wrapped f` and used as `Wrapped Toy` without losing anything. – Cirdec Feb 10 '15 at 18:24
  • This is also a nice case wherein lists-of-existentials are meaningful. Typically things like `[Showable]` are frowned upon since they convey no more information than `[String]`, and unnecessarily use sophisticated types. Here, instead, it _is_ possible to unwrap the existential and recover its actual type, thanks to GADTs pattern matching. – chi Feb 10 '15 at 18:26
  • @dfeuer I guess I won't be able to get away without some wrapping, unwrapping, and lifting functions on `Toy a` up to `WrappedToy`. Thanks! @Cirdec `onInt` looks very much like `fmap`, `(=<<)`, etc… – gspindles Feb 10 '15 at 18:32
  • @dfeuer I got home and had a chance to try this out some more. I was able to write `liftWrap :: (forall a. Toy a -> b) -> WrapToy -> b` with `liftWrap f (Wrap t) = f t`; as well as `mapWrap :: (forall a. Toy a -> b) -> [WrapToy] -> [b]` with `mapWrap f ws = map (liftWrap f) ws`. The compiler nicely warns me about doing `{-# LANGUAGE Rank2Types #-}` , after which, everything works fine. For now, I'm happy with this. Thanks! – gspindles Feb 11 '15 at 04:23
6

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.

Community
  • 1
  • 1
effectfully
  • 12,325
  • 2
  • 17
  • 40
5

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
Cirdec
  • 24,019
  • 2
  • 50
  • 100
  • I don't think this is necessary here (although it is a useful technique!); see the answer I'm about to write. – dfeuer Feb 10 '15 at 18:01
  • @Cirdec This approach looks very interesting. I'll have to learn about datakind promotion before I can tackle the problem this way. Thanks for the suggestion. – gspindles Feb 10 '15 at 18:20
  • @dfeuer The difference between the `HList1` indexed with types and wrapping the data in a universally quantified constructor like in your answer is the universally quantified constructor forgets all type-level knowledge about the contained type. Forgetting the type-level knowledge about the contained type can be useful since it can simplify types. The contained types can be recovered by pattern matching on the `Toy`'s constructors, but can never be reintroduced at the type level. – Cirdec Feb 10 '15 at 18:31
  • 1
    @Cirdec, I think *all* of these ideas demand a richer example application. – dfeuer Feb 10 '15 at 18:33
  • @Cirdec, could you give an example, which illustrates why it can be useful to remember type variables? Besides a trivial stuff like type-safe `head`. Your `zeros` is isomorophic to `zeros :: (Toy Bool, Toy Int); zeros = (TBool False, TInt 0)`. I can imagine some situtations with type-level computations via type families, but Haskell doesn't really handle dependent types properly. – effectfully Feb 10 '15 at 20:07
  • 1
    @user3237465 The big difference between `HList1 Toy [Bool, Int]` and `(Toy Bool, Toy Int)` is that you know that `f` is the same everywhere. For example, you can apply natural transformations `forall a. f a -> g a` to `HList1`s. If [`MFunctor`](https://hackage.haskell.org/package/mmorph-1.0.0/docs/Control-Monad-Morph.html#t:MFunctor) were poly-kinded, I would have provided `hoist` for an `MFunctor` instance. There are other things you can do without touching `TypeFamilies`, like applying functions, zipping lists together, etc. – Cirdec Feb 10 '15 at 20:45
  • Thanks. You can apply natural transformations to existentials too. Or more generally (and probably less useful) `(>>=!) :: Exists p -> (forall x. p x -> Exists q) -> Exists q; This x >>=! f = f x`. Applying functions is a perfect example. – effectfully Feb 10 '15 at 21:22
2

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
Luis Casillas
  • 29,802
  • 7
  • 49
  • 102
  • I have not looked into `Data.Typable`. I'll come back to your example once I looked into it. There are just too many topics to get into and learn. It's rather nice, but I'm a long way off from most of the advanced stuff. – gspindles Feb 10 '15 at 23:15
  • If you're using `GADTs` and `ExistentialQuantification` you're already pretty advanced. But yeah, nothing wrong with pacing yourself. – Luis Casillas Feb 11 '15 at 21:02