[Haskell-cafe] Can I specify the a in a phantom type to be limited to a sum type?

Andras Slemmer 0slemi0 at gmail.com
Fri May 15 09:12:29 UTC 2015


You can do this, although you still need a datastructure that allows you to
use the contained type:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Tutorial where

data Gender = Male | Female deriving (Show)

data Race = White | Black deriving (Show)

type Age = Int

data Answer a where
  Answer :: RacistAgistSexist a => a -> Answer a

deriving instance Show w => Show (Answer w)

data GenderRaceAge
  = Gender Gender
  | Race Race
  | Age Age

class RacistAgistSexist a where
  genderRaceAge :: a -> GenderRaceAge
instance RacistAgistSexist Gender where
  genderRaceAge = Gender
instance RacistAgistSexist Race where
  genderRaceAge = Race
instance RacistAgistSexist Age where
  genderRaceAge = Age

-- You can use genderRaceAge to get a GenderRaceAge out of the contained
type if you don't know 'a'


On 15 May 2015 at 08:51, Tom Ellis <
tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote:

> On Fri, May 15, 2015 at 01:47:49AM -0500, Cody Goodman wrote:
> > How can I create Answers of type Gender, Race, or Age?
> >
> > These should be possible:
> >
> > λ> Answer Male
> > λ> Answer White
> > λ> Answer Black
> > λ> Answer 28
> >
> > Others such as using a string should not be possible:
> >
> > λ> Answer "a string" -- should throw type error
>
> It would probably help if you tell us why precisely you want this, and in
> particular why
>
> data Answer = AnswerGender Gender
>             | AnswerRace   Race
>             | AnswerAge    Int
>
> is not satisfactory.
>
> Tom
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150515/1efebeea/attachment.html>


More information about the Haskell-Cafe mailing list