dak
dak

Reputation: 199

Haskell: list of elements with class restriction

here's my question:

this works perfectly:

type Asdf = [Integer]
type ListOfAsdf = [Asdf]

Now I want to do the same but with the Integral class restriction:

type Asdf2 a = (Integral a) => [a]
type ListOfAsdf2 = (Integral a) => [Asdf2 a]

I got this error:

Illegal polymorphic or qualified type: Asdf2 a
Perhaps you intended to use -XImpredicativeTypes
In the type synonym declaration for `ListOfAsdf2'

I have tried a lot of things but I am still not able to create a type with a class restriction as described above.

Thanks in advance!!! =)

Dak

Upvotes: 5

Views: 299

Answers (2)

AndrewC
AndrewC

Reputation: 32455

If you need a context, the easiest way would be to use a data declaration:

data (Integral a) => IntegralData a = ID [a]
type ListOfIntegralData a = [IntegralData a]

*Main> :t [ ID [1234,1234]]
[ID [1234,1234]] :: Integral a => [IntegralData a]

This has the (sole) effect of making sure an Integral context is added to every function that uses the IntegralData data type.

sumID :: Integral a => IntegralData a -> a
sumID (ID xs) = sum xs

The main reason a type synonym isn't working for you is that type synonyms are designed as just that - something that replaces a type, not a type signature.

But if you want to go existential the best way is with a GADT, because it handles all the quantification issues for you:

{-# LANGUAGE GADTs #-}

data IntegralGADT where
   IG :: Integral a => [a] -> IntegralGADT 
type ListOfIG = [ IntegralGADT ]

Because this is essentially an existential type, you can mix them up:

*Main> :t [IG [1,1,1::Int], IG [234,234::Integer]]
[IG [1,1,1::Int],IG [234,234::Integer]] :: [ IntegralGADT ]

Which you might find quite handy, depending on your application.

The main advantage of a GADT over a data declaration is that when you pattern match, you implicitly get the Integral context:

showPointZero :: IntegralGADT -> String
showPointZero (IG xs) = show $ (map fromIntegral xs :: [Double])

*Main> showPointZero (IG [1,2,3])
"[1.0,2.0,3.0]"

But existential quantification is sometimes used for the wrong reasons, (eg wanting to mix all your data up in one list because that's what you're used to from dynamically typed languages, and you haven't got used to static typing and its advantages yet).

Here I think it's more trouble than it's worth, unless you need to mix different Integral types together without converting them. I can't see a reason why this would help, because you'll have to convert them when you use them.

For example, you can't define

unIG (IG xs) = xs

because it doesn't even type check. Rule of thumb: you can't do stuff that mentions the type a on the right hand side.

However, this is OK because we convert the type a:

unIG :: Num b => IntegralGADT -> [b]
unIG (IG xs) = map fromIntegral xs

Here existential quantification has forced you convert your data when I think your original plan was to not have to! You may as well convert everything to Integer instead of this.

If you want things simple, keep them simple. The data declaration is the simplest way of ensuring you don't put data in your data type unless it's already a member of some type class.

Upvotes: 5

Thomas M. DuBuisson
Thomas M. DuBuisson

Reputation: 64740

Ranting Against the Anti-Existentionallists

I always dislike the anti-existential type talk in Haskell as I often find existentials useful. For example, in some quick check tests I have code similar to (ironically untested code follows):

data TestOp = forall a. Testable a => T String a

tests :: [TestOp]
tests = [T "propOne:" someProp1
        ,T "propTwo:" someProp2
        ]

runTests = mapM runTest tests
runTest (T s a) = putStr s >> quickCheck a

And even in a corner of some production code I found it handy to make a list of types I'd need random values of:

type R a = Gen -> (a,Gen)
data RGen = forall a. (Serialize a, Random a) => RGen (R a)
list = [(b1, str1, random :: RGen (random :: R Type1))
       ,(b2, str2, random :: RGen (random :: R Type2))
       ]

Answering Your Question

{-# LANGUAGE ExistentialQuantification #-}
data SomeWrapper = forall a. Integral a => SW a

Upvotes: 5

Related Questions