[Haskell-cafe] Re: A Question of Restriction

Gleb Alexeyev gleb.alexeev at gmail.com
Mon Jul 27 04:31:13 EDT 2009


Brian Troutwine wrote:
>> Do you have any reason not to do the above?
> 
> Yes, the subset types that I wish to define are not clean partitions,
> though my example does suggest this. Let's say that the definition of
> Foo is now
> 
>   data Foo = One | Two | Three | Four | Five | Six
> 
> while Odd and Even remain the same. I would further like to define
> Triangular, which I will do incorrectly for consistency.
> 
>   data Triangular = One | Three | Six
> 
> I could not accommodate this definition using your scheme, correct?
> 

A variation on scheme proposed by Ross Mellgren earlier in this thread.
It's a bit tedious but allows for definition of arbitrary subsets thus 
it may work for you:

{-# LANGUAGE GADTs, EmptyDataDecls  #-}

data One
data Two
data Three
data Four

data Foo a where
     FOne :: Foo One
     FTwo :: Foo Two
     FThree :: Foo Three
     FFour :: Foo Four


class IsEven a
instance IsEven Two
instance IsEven Four

class IsOdd a
instance IsOdd One
instance IsOdd Three

class IsLessThanThree a
instance IsLessThanThree One
instance IsLessThanThree Two

quux :: IsEven a => Foo a -> String
quux FTwo = "2"
quux FFour = "4"

bzzt :: IsLessThanThree a => Foo a -> String
bzzt FOne = "1"
bzzt FTwo = "2"






More information about the Haskell-Cafe mailing list