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

Cody Goodman codygman.consulting at gmail.com
Fri May 15 06:47:49 UTC 2015


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


{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
module Tutorial where

data Gender = Male | Female deriving (Show)

data Race = White | Black deriving (Show)

type Age = Int

data Answer a where
  Answer ::  Gender ->  Answer Gender

deriving instance Show (Answer w)

-- λ> -- This is pretty useful and accepts Answers with the Gender
-- λ> Answer Male
-- Answer Male
-- λ> :t Answer Male
-- Answer Male :: Answer Gender
-- λ> -- how do I also accept Race and Age?

-- below I try to sort out how to use type families (unsuccessfully) before bed
-- type family Answer :: *
-- type instance Answer Gender = Answer Gender


More information about the Haskell-Cafe mailing list