How to change the behavior of the function based on class constraints in Haskell? - haskell

I have a data type that represents a collection of values paired with a probability. At first, the implementation was just to use good old lists, but as you can imagine, this can be inefficient (for example, I use a Tree instead of a list to store ordered values)
After some research, I thought about using GADTs
data Tree a b = Leaf | Node {left::Tree a b, val :: (a, b), right :: Tree a b}
data Prob a where
POrd ::Ord a => Tree a Rational -> Prob a
PEq ::Eq a => [(a, Rational)] -> Prob a
PPlain ::[(a, Rational)] -> Prob a
So far, so good. I'm now stuck at trying to create a smart constructor for my new data type,
that takes [(a,Rational)] and depending on the constraints of a, chooses the correct constructor for Prob. Basically:
prob :: [(a, Rational)] -> Prob a
-- chooses the "best" constructor based on the constraints of a
Is this at all possible? If not, how should I go about designing something better? Am I missing something?
Thanks!

There is no way to perform a check of the form "is type T in class C?" in Haskell. The issue here is that it is hard to answer negatively to such question and allow separate compilation: T could be in C in the scope of one module but not in the scope of another one, causing a rather fragile semantics.
To ensure consistency, Haskell only allows to require a constraint, and raise an compile time error otherwise.
As far as I can see, the best you can do is to use another custom type class, which tells you which case is the best one. E.g.
{-# LANGUAGE AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables #-}
data BestConstraint a where
BCOrd :: Ord a => BestConstraint a
BCEq :: Eq a => BestConstraint a
BCNone :: BestConstraint a
class BC a where
bestC :: BestConstraint a
instance BC Int where bestC = BCOrd
-- ... etc.
instance BC a => BC [a] where
bestC = case bestC #a of
BCOrd -> BCOrd
BCEq -> BCEq
BCNone -> BCNone
prob :: forall a . BestConstraint a => [(a, Rational)] -> Prob a
prob xs = case bestC #a of
BCOrd -> POrd .... -- build the tree
BCEq -> PEq xs
BCNone -> PPlain xs
You will have to provide an instance for any type you want to use, though.

Related

Resolving ambiguity in MultiParameterTypeClass

Based on the feedback to this question, I've used a MultiParamTypeClass to represent a reinforcement learning environment Environment, using 3 type variables: e for the environment instance itself (e.g. a game like Nim, below), s for the state data type used by the specific game, and a for the action data type used by the specific game.
{-# LANGUAGE MultiParamTypeClasses #-}
class MultiAgentEnvironment e s a where
baseState :: e -> s
nextState :: e -> s -> a -> s
reward :: (Num r) => e -> s -> a -> [r]
data Game = Game { players :: Int
, initial_piles :: [Int]
} deriving (Show)
data State = State { player :: Int
, piles :: [Int]} deriving (Show)
data Action = Action { removed :: [Int]} deriving (Show)
instance MultiAgentEnvironment Game State Action where
baseState game = State{player=0, piles=initial_piles game}
nextState game state action = State{player=player state + 1 `mod` players game,
piles=zipWith (-) (piles state) (removed action)}
reward game state action = [0, 0]
newGame :: Int -> [Int] -> Game
newGame players piles = Game{players=players, initial_piles=piles}
main = do
print "Hello, world!"
let game = newGame 2 [3,4,5]
print game
As expected, I'm running into ambiguity issues already. See below, where the action type variable a is deemed ambiguous within the typeclass Environment.
(base) randm#soundgarden:~/Projects/games/src/Main$ ghc -o basic basic.hs
[1 of 1] Compiling Main ( basic.hs, basic.o )
basic.hs:4:5: error:
• Could not deduce (MultiAgentEnvironment e s a0)
from the context: MultiAgentEnvironment e s a
bound by the type signature for:
baseState :: forall e s a. MultiAgentEnvironment e s a => e -> s
at basic.hs:4:5-23
The type variable ‘a0’ is ambiguous
• In the ambiguity check for ‘baseState’
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
When checking the class method:
baseState :: forall e s a. MultiAgentEnvironment e s a => e -> s
In the class declaration for ‘MultiAgentEnvironment’
|
4 | baseState :: e -> s
| ^^^^^^^^^^^^^^^^^^^
How do I resolve this ambiguity? Am I mistakenly using typeclasses to implement interfaces (i.e. baseState, nextState, reward)?
While you could turn on AllowAmbiguousTypes, that will only push your problem further down the road. That is, eventually, you'll try to call baseState, and GHC will need to know what a is. There are three good options you have:
Use functional dependencies,
Use associated type families, or
Don't use a class for this.
Let's look at each option in detail.
Functional Dependencies
The problem that GHC is having is that it knows which e and s you want to use when you call a function like baseState (it can determine those from the input and output of the baseState function), but it doesn't know which a to use. For all GHC knows, there may be multiple instantiations of MultiAgentEnvironment that could work for a given e and s. With functional dependencies, you can tell GHC that a given e and s totally define what the a should be. In plain English, by putting in a functional dependency on a, you're saying that for any given environment and state, there is only one possible action type that makes sense. If this is true, then you add them like so:
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
class MultiAgentEnvironment e s a | e s -> a where
baseState :: e -> s
nextState :: e -> s -> a -> s
reward :: (Num r) => e -> s -> a -> [r]
Since each one of your functions have e and s in them, a is the only type parameter that could have been ambiguous, and with this fundep, it's not ambiguous anymore. That said, if you know that the environment type determines both the state and action unambiguously (that is, a given environment can only ever have one possible state and action type), then you can use two fundeps to lower the ambiguity even more, as in:
class MultiAgentEnvironment e s a | e -> s a where
Associated Type Families
Functional Dependencies have a bit of a bad reputation, and the more modern alternative is typically to use associated type families. In practice, for your purposes, they work very similarly. Once again, you have to be okay with the environment type determining the action type (and, perhaps, the state type). If so, you write it like this:
{-# LANGUAGE TypeFamilies #-}
class MultiAgentEnvironment e where
type EState e
type EAction e
baseState :: e -> EState e
nextState :: e -> EState e -> a -> EState e
reward :: (Num r) => e -> EState e -> EAction e -> [r]
Then, when you create your instance, it will look like:
instance MultiAgentEnvironment Game where
type EState Game = State
type EAction Game = Action
baseState game = State{player=0, piles=initial_piles game}
nextState game state action = ...
Use a Data Type Instead Of a Class
The last option is to forgo using a type class altogether. Instead, you can make the data explicit by just representing it as a data type. For instance, you can define:
{-# LANGUAGE RankNTypes #-}
data MultiAgentEnvironment e s a = MultiAgentEnvironment
{ baseState :: e -> s
, nextState :: e -> s -> a -> s
, reward :: forall r. (Num r) => e -> s -> a -> [r]
}
Instead of making an instance of the type class, you just make a value of the data type:
gameStateActionMAE :: MultiAgentEnvironment Game State Action
gameStateActionMAE = MultiAgentEnvironment
{ baseState = \game -> State{player=0, piles=initial_piles game}
, nextState = \game state action -> State{player=player state + 1 `mod` players game,
piles=zipWith (-) (piles state) (removed action)}
, reward = \game state action -> [0, 0]
}
One nice advantage of this method is that you can make multiple different MultiAgentEnvironments with the same types but that have different behaviors. Using them is pretty simple too: instead of having MultiAgentEnvironment e s a as a constraint, you now have it as just a regular old argument. In fact, if you turn on the RecordWildCards pragma, then any function that used to start with
foo :: MultiAgentEnvironment e s a => x -> y
foo x = ...
can now be written as
foo :: MultiAgentEnvironment e s a -> x -> y
foo mae#MultiAgentEnvironment{..} x = ...
and the body should be pretty much identical (well, unless the body calls a subfunction which requires the MultiAgentEnvironment, in which case you'll need to manually pass mae along).

Type Constraint in Constructor [duplicate]

This question already has answers here:
Type Constraints in Data Declaration Haskell
(3 answers)
Closed 3 years ago.
I am trying to make a normal form game solver for game theory, and I'm trying to make it as generic as possible for good practice and for my own convenience. I would like to use the same functions to solve both zero-sum and non-zero-sum games, so I am using the following data type:
data Payoffs = (Num a, Eq a, Ord a) => ZS a
| (Num a, Eq a, Ord a) => NZS (a,a)
However, this is not correct syntax. Is there any way to constrain a so that it must satisfy those type constraints?
Short answer (and probably not the one you need):
To make your code work as is, you need a forall quantifier (for which you need to enable ExistentialQuantification):
{-# LANGUAGE ExistentialQuantification #-}
data Payoffs =
forall a. (Num a, Eq a, Ord a) => ZS a
| forall a. (Num a, Eq a, Ord a) => NZS (a,a)
If you have a type variable in the data constructor (i.e. ZS a), then you have two choices: either that variable has to appear in the type constructor (i.e. data Payoffs a =), or you need to say "I don't care what type it is, as long as it supports these classes" - which is achieved via the forall quantifier.
But this looks kinda useless to me, which suggests that you may be misunderstanding what it means. If you write the above code, every value of your Payoffs type will be able to wrap a value of any type, as long as that type supports Num, Eq, and Ord. One subtle consequence of this is that, if you have two values of Payoffs lying around, they will not necessarily wrap the same type. For example:
let x = ZS (42 :: Int) -- wraps an Int
let y = NZS (2.71 :: Double, 3.14) -- wraps two Doubles
This means that, upon unpacking them, you won't be able to, for example, add them together, because, even though they both implement Num, the compiler doesn't have any proof that they're actually the same type.
What I suspect you actually need is a parametrized type, like this:
data Payoffs a = ZS a | NZS (a, a)
But then, of course, you lose the constraints: anybody can go and create ZS String or something. You can use the GADT syntax (with the GADTs extension) to bring them back:
{-# LANGUAGE GADTs #-}
data Payoffs a where
ZS :: (Num a, Ord a, Eq a) => a -> Payoffs a
NZS :: (Num a, Ord a, Eq a) => (a, a) -> Payoffs a
This notation is equivalent to ZS a | NZS (a, a), except you get to define each constructor with the same syntax as any function - including constraints. A type defined like this won't allow for creating values of type Payoffs a unless a satisfies the constraints.
At the same time, if you have a value of a type like this lying around, you know what type it wraps inside. And this allows you to tell if two Payoffs values wrap the same type or different. And then, if you know that they're the same, you can do things with them using the supported classes, for example:
addPayoffs :: Payoffs a -> Payoffs a -> Payoffs a
addPayoffs (ZS a) (ZS b) = ZS (a + b)
addPayoffs (ZS a) (NZS (x,y)) = NZS (a+x, a+y)
... etc.

Defining a Function for Multiple Types

How is a function defined for different types in Haskell?
Given
func :: Integral a => a -> a
func x = x
func' :: (RealFrac a , Integral b) => a -> b
func' x = truncate x
How could they be combined into one function with the signature
func :: (SomeClassForBoth a, Integral b) => a -> b
With a typeclass.
class TowardsZero a where towardsZero :: Integral b => a -> b
instance TowardsZero Int where towardsZero = fromIntegral
instance TowardsZero Double where towardsZero = truncate
-- and so on
Possibly a class with an associated type family constraint is closer to what you wrote (though perhaps not closer to what you had in mind):
{-# LANGUAGE TypeFamilies #-}
import GHC.Exts
class TowardsZero a where
type RetCon a b :: Constraint
towardsZero :: RetCon a b => a -> b
instance TowardsZero Int where
type RetCon Int b = Int ~ b
towardsZero = id
instance TowardsZero Double where
type RetCon Double b = Integral b
towardsZero = truncate
-- and so on
This is known as ad hoc polymorphism, where you execute different code depending on the type. The way this is done in Haskell is using typeclasses. The most direct way is to define a new class
class Truncable a where
trunc :: Integral b => a -> b
And then you can define several concrete instances.
instance Truncable Integer where trunc = fromInteger
instance Truncable Double where trunc = truncate
This is unsatisfying because it requires an instance for each concrete type, when there are really only two families of identical-looking instances. Unfortunately, this is one of the cases where it is hard to reduce boilerplate, for technical reasons (being able to define "instance families" like this interferes with the open-world assumption of typeclasses, among other difficulties with type inference). As a hint of the complexity, note that your definition assumes that there is no type that is both RealFrac and Integral, but this is not guaranteed -- which implementation should we pick in this case?
There is another issue with this typeclass solution, which is that the Integral version doesn't have the type
trunc :: Integral a => a -> a
as you specified, but rather
trunc :: (Integral a, Integral b) => a -> b
Semantically this is not a problem, as I don't believe it is possible to end up with some polymorphic code where you don't know whether the type you are working with is Integral, but you do need to know that when it is, the result type is the same as the incoming type. That is, I claim that whenever you would need the former rather than the latter signature, you already know enough to replace trunc by id in your source. (It's a gut feeling though, and I would love to be proven wrong, seems like a fun puzzle)
There may be performance implications, however, since you might unnecessarily call fromIntegral to convert a type to itself, and I think the way around this is to use {-# RULES #-} definitions, which is a dark scary bag of complexity that I've never really dug into, so I don't know how hard or easy this is.
I don't recommend this, but you can hack at it with a GADT:
data T a where
T1 :: a -> T a
T2 :: RealFrac a => a -> T b
func :: Integral a => T a -> a
func (T1 x) = x
func (T2 x) = truncate x
The T type says, "Either you already know the type of the value I'm wrapping up, or it's some unknown instance of RealFrac". The T2 constructor existentially quantifies a and packs up a RealFrac dictionary, which we use in the second clause of func to convert from (unknown) a to b. Then, in func, I'm applying an Integral constraint to the a which may or may not be inside the T.

Why constraints on data are a bad thing?

I know this question has been asked and answered lots of times but I still don't really understand why putting constraints on a data type is a bad thing.
For example, let's take Data.Map k a. All of the useful functions involving a Map need an Ord k constraint. So there is an implicit constraint on the definition of Data.Map. Why is it better to keep it implicit instead of letting the compiler and programmers know that Data.Map needs an orderable key.
Also, specifying a final type in a type declaration is something common, and one can see it as a way of "super" constraining a data type.
For example, I can write
data User = User { name :: String }
and that's acceptable. However is that not a constrained version of
data User' s = User' { name :: s }
After all 99% of the functions I'll write for the User type don't need a String and the few which will would probably only need s to be IsString and Show.
So, why is the lax version of User considered bad:
data (IsString s, Show s, ...) => User'' { name :: s }
while both User and User' are considered good?
I'm asking this, because lots of the time, I feel I'm unnecessarily narrowing my data (or even function) definitions, just to not have to propagate constraints.
Update
As far as I understand, data type constraints only apply to the constructor and don't propagate. So my question is then, why do data type constraints not work as expected (and propagate)? It's an extension anyway, so why not have a new extension doing data properly, if it was considered useful by the community?
TL;DR:
Use GADTs to provide implicit data contexts.
Don't use any kind of data constraint if you could do with Functor instances etc.
Map's too old to change to a GADT anyway.
Scroll to the bottom if you want to see the User implementation with GADTs
Let's use a case study of a Bag where all we care about is how many times something is in it. (Like an unordered sequence. We nearly always need an Eq constraint to do anything useful with it.
I'll use the inefficient list implementation so as not to muddy the waters over the Data.Map issue.
GADTs - the solution to the data constraint "problem"
The easy way to do what you're after is to use a GADT:
Notice below how the Eq constraint not only forces you to use types with an Eq instance when making GADTBags, it provides that instance implicitly wherever the GADTBag constructor appears. That's why count doesn't need an Eq context, whereas countV2 does - it doesn't use the constructor:
{-# LANGUAGE GADTs #-}
data GADTBag a where
GADTBag :: Eq a => [a] -> GADTBag a
unGADTBag (GADTBag xs) = xs
instance Show a => Show (GADTBag a) where
showsPrec i (GADTBag xs) = showParen (i>9) (("GADTBag " ++ show xs) ++)
count :: a -> GADTBag a -> Int -- no Eq here
count a (GADTBag xs) = length.filter (==a) $ xs -- but == here
countV2 a = length.filter (==a).unGADTBag
size :: GADTBag a -> Int
size (GADTBag xs) = length xs
ghci> count 'l' (GADTBag "Hello")
2
ghci> :t countV2
countV2 :: Eq a => a -> GADTBag a -> Int
Now we didn't need the Eq constraint when we found the total size of the bag, but it didn't clutter up our definition anyway. (We could have used size = length . unGADTBag just as well.)
Now lets make a functor:
instance Functor GADTBag where
fmap f (GADTBag xs) = GADTBag (map f xs)
oops!
DataConstraints_so.lhs:49:30:
Could not deduce (Eq b) arising from a use of `GADTBag'
from the context (Eq a)
That's unfixable (with the standard Functor class) because I can't restrict the type of fmap, but need to for the new list.
Data Constraint version
Can we do as you asked? Well, yes, except that you have to keep repeating the Eq constraint wherever you use the constructor:
{-# LANGUAGE DatatypeContexts #-}
data Eq a => EqBag a = EqBag {unEqBag :: [a]}
deriving Show
count' a (EqBag xs) = length.filter (==a) $ xs
size' (EqBag xs) = length xs -- Note: doesn't use (==) at all
Let's go to ghci to find out some less pretty things:
ghci> :so DataConstraints
DataConstraints_so.lhs:1:19: Warning:
-XDatatypeContexts is deprecated: It was widely considered a misfeature,
and has been removed from the Haskell language.
[1 of 1] Compiling Main ( DataConstraints_so.lhs, interpreted )
Ok, modules loaded: Main.
ghci> :t count
count :: a -> GADTBag a -> Int
ghci> :t count'
count' :: Eq a => a -> EqBag a -> Int
ghci> :t size
size :: GADTBag a -> Int
ghci> :t size'
size' :: Eq a => EqBag a -> Int
ghci>
So our EqBag count' function requires an Eq constraint, which I think is perfectly reasonable, but our size' function also requires one, which is less pretty. This is because the type of the EqBag constructor is EqBag :: Eq a => [a] -> EqBag a, and this constraint must be added every time.
We can't make a functor here either:
instance Functor EqBag where
fmap f (EqBag xs) = EqBag (map f xs)
for exactly the same reason as with the GADTBag
Constraintless bags
data ListBag a = ListBag {unListBag :: [a]}
deriving Show
count'' a = length . filter (==a) . unListBag
size'' = length . unListBag
instance Functor ListBag where
fmap f (ListBag xs) = ListBag (map f xs)
Now the types of count'' and show'' are exactly as we expect, and we can use standard constructor classes like Functor:
ghci> :t count''
count'' :: Eq a => a -> ListBag a -> Int
ghci> :t size''
size'' :: ListBag a -> Int
ghci> fmap (Data.Char.ord) (ListBag "hello")
ListBag {unListBag = [104,101,108,108,111]}
ghci>
Comparison and conclusions
The GADTs version automagically propogates the Eq constraint everywhere the constructor is used. The type checker can rely on there being an Eq instance, because you can't use the constructor for a non-Eq type.
The DatatypeContexts version forces the programmer to manually propogate the Eq constraint, which is fine by me if you want it, but is deprecated because it doesn't give you anything more than the GADT one does and was seen by many as pointless and annoying.
The unconstrained version is good because it doesn't prevent you from making Functor, Monad etc instances. The constraints are written exactly when they're needed, no more or less. Data.Map uses the unconstrained version partly because unconstrained is generally seen as most flexible, but also partly because it predates GADTs by some margin, and there needs to be a compelling reason to potentially break existing code.
What about your excellent User example?
I think that's a great example of a one-purpose data type that benefits from a constraint on the type, and I'd advise you to use a GADT to implement it.
(That said, sometimes I have a one-purpose data type and end up making it unconstrainedly polymorphic just because I love to use Functor (and Applicative), and would rather use fmap than mapBag because I feel it's clearer.)
{-# LANGUAGE GADTs #-}
import Data.String
data User s where
User :: (IsString s, Show s) => s -> User s
name :: User s -> s
name (User s) = s
instance Show (User s) where -- cool, no Show context
showsPrec i (User s) = showParen (i>9) (("User " ++ show s) ++)
instance (IsString s, Show s) => IsString (User s) where
fromString = User . fromString
Notice since fromString does construct a value of type User a, we need the context explicitly. After all, we composed with the constructor User :: (IsString s, Show s) => s -> User s. The User constructor removes the need for an explicit context when we pattern match (destruct), becuase it already enforced the constraint when we used it as a constructor.
We didn't need the Show context in the Show instance because we used (User s) on the left hand side in a pattern match.
Constraints
The problem is that constraints are not a property of the data type, but of the algorithm/function that operates on them. Different functions might need different and unique constraints.
A Box example
As an example, let's assume we want to create a container called Box which contains only 2 values.
data Box a = Box a a
We want it to:
be showable
allow the sorting of the two elements via sort
Does it make sense to apply the constraint of both Ord and Show on the data type? No, because the data type in itself could be only shown or only sorted and therefore the constraints are related to its use, not it's definition.
instance (Show a) => Show (Box a) where
show (Box a b) = concat ["'", show a, ", ", show b, "'"]
instance (Ord a) => Ord (Box a) where
compare (Box a b) (Box c d) =
let ca = compare a c
cb = compare b d
in if ca /= EQ then ca else cb
The Data.Map case
Data.Map's Ord constraints on the type is really needed only when we have > 1 elements in the container. Otherwise the container is usable even without an Ord key. For example, this algorithm:
transf :: Map NonOrd Int -> Map NonOrd Int
transf x =
if Map.null x
then Map.singleton NonOrdA 1
else x
Live demo
works just fine without the Ord constraint and always produce a non empty map.
Using DataTypeContexts reduces the number of programs you can write. If most of those illegal programs are nonsense, you might say it's worth the runtime cost associated with ghc passing in a type class dictionary that isn't used. For example, if we had
data Ord k => MapDTC k a
then #jefffrey's transf is rejected. But we should probably have transf _ = return (NonOrdA, 1) instead.
In some sense the context is documentation that says "every Map must have ordered keys". If you look at all of the functions in Data.Map you'll get a similar conclusion "every useful Map has ordered keys". While you can create maps with unordered keys using
mapKeysMonotonic :: (k1 -> k2) -> Map k1 a -> Map k2 a
singleton :: k2 a -> Map k2 a
But the moment you try to do anything useful with them, you'll wind up with No instance for Ord k2 somewhat later.

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
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
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.

Resources