Illegal instance declaration / Overlapping instances - haskell

Given class X and Y, what's the most idiomatic approach to creating instances of each other's class? e.g. -
instance (X a) => Y a where ...
instance (Y a) => X a where ...
I'd like to avoid extensions. Also, I am aware that this could cause some nasty infinite recursion, so I'm open to a completely different approach to accomplish the same thing and stay relatively DRY. Below gives some context as to the exact problem I am having -
data Dealer = Dealer Hand
data Player = Player Hand Cash
class HasPoints a where
getPoints :: a -> Int
class (HasPoints a) => CardPlayer a where
getHand :: a -> Hand
viewHand :: a -> TurnIsComplete -> Hand
hasBlackjack :: a -> Bool
hasBlackjack player = getPoints player == 21 &&
(length . getCards . getHand) player == 2
busts :: a -> Bool
busts player = getPoints player > 21
I'd like to do this -
instance (CardPlayer a) => HasPoints a where
getPoints = getPoints . getHand
But it seems I must do this -
instance HasPoints Dealer where
getPoints = getPoints . getHand
instance HasPoints Player where
getPoints = getPoints . getHand
EDIT
Seems my favorite approach is to keep the HasPoints typeclass and implement CardPlayer as data instead.
data CardPlayer = Dealer Hand | Player Hand Cash
instance HasPoints CardPlayer where
getPoints = getPoints . getHand
getCash :: CardPlayer -> Maybe Cash
getHand :: CardPlayer -> Hand
viewHand :: CardPlayer -> TurnIsComplete -> Hand
hasBlackjack :: CardPlayer -> Bool
busts :: CardPlayer -> Bool
-- I wanted HasPoints to be polymorphic
-- so it could handle Card, Hand, and CardPlayer
instance HasPoints Hand where
getPoints Hand { getCards = [] } = 0
getPoints hand = if base > 21 && numAces > 0
then maximum $ filter (<=21) possibleScores
else base
where base = sum $ map getPoints $ getCards hand
numAces = length $ filter ((Ace==) . rank) $ getCards hand
possibleScores = map ((base-) . (*10)) [1..numAces]
instance HasPoints Card where
-- You get the point

Given class X and Y, what's the most idiomatic approach to creating instances of each other's class?
The most idiomatic approach, given your example code, is to not use type classes in the first place when they're not doing anything useful. Consider the types of the class functions:
class HasPoints a where
getPoints :: a -> Int
class (HasPoints a) => CardPlayer a where
getHand :: a -> Hand
viewHand :: a -> TurnIsComplete -> Hand
hasBlackjack :: a -> Bool
busts :: a -> Bool
What do they have in common? They all take exactly one value of the class parameter type as their first argument, so given such a value we can apply each function to it and get all the same information without needing to bother with a class constraint.
So if you want a nice, idiomatic DRY approach, consider this:
data CardPlayer a = CardPlayer
{ playerPoints :: Int
, hand :: Hand
, viewHand :: TurnIsComplete -> Hand
, hasBlackjack :: Bool
, busts :: Bool
, player :: a
}
data Dealer = Dealer
data Player = Player Cash
In this version, the types CardPlayer Player and CardPlayer Dealer are equivalent to the Player and Dealer types you had. The player record field here is used to get the data specialized to the kind of player, and functions that would have been polymorphic with a class constraint in yours can simply operate on values of type CardPlayer a.
Though perhaps it would make more sense for hasBlackjack and busts to be regular functions (like your default implementations), unless you really need to model players who are immune to the standard rules of Blackjack.
From this version, you can now define a HasPoints class alone if you have very different types that should be instances of it, though I'm skeptical of the utility of that, or you can apply the same transformation to get another layer:
data HasPoints a = HasPoints
{ points :: Int
, pointOwner :: a
}
However, this approach quickly becomes unwieldy the further you nest specializations like this.
I would suggest droping HasPoints entirely. It only has one function, which just extracts an Int, so any code that handles HasPoints instances generically might as well just use Ints and be done with it.

In general, it's impossible to declare all instances of a class to also be instances of another class without making type checking undecidable. So your proposed definition will only work with UndecidableInstances enabled:
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
instance (CardPlayer a) => HasPoints a where
getPoints = getPoints . getHand
Although it's possible to go that route, I'd suggest refactoring the code as follows instead:
data Hand = ...
handPoints :: Hand -> Int
handPoints = ...
data Dealer = Dealer Hand
data Player = Player Hand Cash
class CardPlayer a where
getHand :: a -> Hand
...
instance CardPlayer Dealer where ...
instance CardPlayer Player where ...
playerPoints :: (CardPlayer a) => a -> Int
playerPoints = handPoints . getHand

Related

A lens for getting or setting a record field determined by a runtime argument

I have these types (and more):
data Player = PlayerOne | PlayerTwo deriving (Eq, Show, Read, Enum, Bounded)
data Point = Love | Fifteen | Thirty deriving (Eq, Show, Read, Enum, Bounded)
data PointsData =
PointsData { pointsToPlayerOne :: Point, pointsToPlayerTwo :: Point }
deriving (Eq, Show, Read)
I'm doing the Tennis kata, and as part of the implementation, I'd like to use some functions that enable me to get or set the points for an arbitrary player, only known at runtime.
Formally, I need functions like these:
pointFor :: PointsData -> Player -> Point
pointFor pd PlayerOne = pointsToPlayerOne pd
pointFor pd PlayerTwo = pointsToPlayerTwo pd
pointTo :: PointsData -> Player -> Point -> PointsData
pointTo pd PlayerOne p = pd { pointsToPlayerOne = p }
pointTo pd PlayerTwo p = pd { pointsToPlayerTwo = p }
As demonstrated, my problem isn't that I can't implement these functions.
They do, however, look lens-like to me, so I wonder if I could get that functionality via the lens library?
Most of the lens tutorials show how to get or set a particular, named part of a bigger data structure. This doesn't quite seem to fit what I'm trying to do here; rather, I'm trying to get or set a sub-part determined at runtime.
An excursion into somewhat abstract typeclasses. Your PointsData has a special relationship with the Player type. It's a bit like a Map Player Point, with the particularity that for every possible value of Player, there's always a corresponding Point. In a way, PointsData is like a "reified function" Player -> Point.
If we make PointsData polymorphic on the type of Points, it would fit with the Representable typeclass. We would say that PointsData is "represented" by Player.
Representable is often useful as an interface to tabular data, like in the grids package.
So one possible solution would be to turn PointsData into an actual Map, but hide the implementation behind a smart constructor that took a Player -> Point function to initialize it for all possible keys (it would correspond to the tabulate method of Representable).
The user should not be able to delete keys from the map. But we could piggyback on the Ixed instance of Map to provide traversals.
import Control.Lens
import Data.Map.Strict -- from "containers"
newtype PointsData = PointsData { getPoints :: Map Player Point }
init :: (Player -> Point) -> PointsData
init f = PointsData (Data.Map.Strict.fromList ((\p -> (p, f p)) <$> [minBound..maxBound]))
playerPoints :: Player -> Lens' PointsData Point
playerPoints pl = Control.Lens.singular (iso getPoints PointsData . ix pl)
You could create a function that produces a Lens given a Player, like this:
playerPoints :: Player -> Lens' PointsData Point
playerPoints PlayerOne = field #"pointsToPlayerOne"
playerPoints PlayerTwo = field #"pointsToPlayerTwo"
(this is using field from generic-lens)
Usage would be like this:
pts :: PointsData
pl1 = pts ^. playerPoints PlayerOne
pl2 = pts ^. playerPoints PlayerTwo
newPts = pts & playerPoints PlayerOne .~ 42
P.S. Or were you looking for picking a field of PointsData by matching field name to Player constructor name? That is also possible via Generic, but doesn't seem worth the trouble.
Based on the answer from Fyodor Soikin and comment from duplode, I ended up using makeLenses from lens and writing a function that returns the appropriate lens:
data PointsData =
PointsData { _pointsToPlayerOne :: Point, _pointsToPlayerTwo :: Point }
deriving (Eq, Show, Read)
makeLenses ''PointsData
playerPoint :: Player -> Lens' PointsData Point
playerPoint PlayerOne = pointsToPlayerOne
playerPoint PlayerTwo = pointsToPlayerTwo
It can be used like this fragment of a bigger function:
score :: Score -> Player -> Score
-- ..
score (Points pd) winner = Points $ pd & playerPoint winner %~ succ
-- ..

On Haskell, what is the linguistic way to represent a card effect for a card game?

I have a simple one-player Card Game:
data Player = Player {
_hand :: [Card],
_deck :: [Card],
_board :: [Card]}
$(makeLenses ''Player)
Some cards have an effect. For example, "Erk" is a card with the following effect:
Flip a coin. If heads, shuffle your deck.
I've implemented it as such:
shuffleDeck :: (MonadRandom m, Functor m) => Player -> m Player
shuffleDeck = deck shuffleM
randomCoin :: (MonadRandom m) => m Coin
randomCoin = getRandom
flipCoin :: (MonadRandom m) => m a -> m a -> m a
flipCoin head tail = randomCoin >>= branch where
branch Head = head
branch Tail = tail
-- Flip a coin. If heads, shuffle your deck.
erk :: (MonadRandom m, Functor m) => Player -> m Player
erk player = flipCoin (deck shuffleM player) (return player)
While this certainly does the job, I find an issue on the forced coupling to the Random library. What if I later on have a card that depends on another monad? Then I'd have to rewrite the definition of every card defined so far (so they have the same type). I'd prefer a way to describe the logic of my game entirely independent from the Random (and any other). Something like that:
erk :: CardAction
erk = do
coin <- flipCoin
case coin of
Head -> shuffleDeck
Tail -> doNothing
I could, later on, have a runGame function that does the connection.
runGame :: (RandomGen g) => g -> CardAction -> Player -> Player
I'm not sure that would help. What is the correct, linguistic way to deal with this pattern?
This is one of the engineering problems the mtl library was designed to solve. It looks like you're already using it, but don't realize its full potential.
The idea is to make monad transformer stacks easier to work with using typeclasses. A problem with normal monad transformer stacks is that you have to know all of the transformers you're using when you write a function, and changing the stack of transformers changes how lifts work. mtl solves this by defining a typeclass for each transformer it has. This lets you write functions that have a class constraint for each transformer it requires but can work on any stack of transformers that includes at least those.
This means that you can freely write functions with different sets of constraints and then use them with your game monad, as long as you game monad has at least those capabilities.
For example, you could have
erk :: MonadRandom m => ...
incr :: MonadState GameState m => ...
err :: MonadError GameError m => ...
lots :: (MonadRandom m, MonadState GameState m) => ...
and define your Game a type to support all of those:
type Game a = forall g. RandT g (StateT GameState (ErrorT GameError IO)) a
You'd be able to use all of these interchangeably within Game, because Game belongs to all of those typeclasses. Moreover, you wouldn't have to change anything except the definition of Game if you wanted to add more capabilities.
There's one important limitation to keep in mind: you can only access one instance of each transformer. This means that you can only have one StateT and one ErrorT in your whole stack. This is why StateT uses a custom GameState type: you can just put all of the different things you may want to store throughout your game into that one type so that you only need one StateT. (GameError does the same for ErrorT.)
For code like this, you can get away with just using the Game type directly when you define your functions:
flipCoin :: Game a -> Game a -> Game a
flipCoin a b = ...
Since getRandom has a type polymorphic over m itself, it will work with whatever Game happens to be as long as it has at least a RandT (or something equivalent) inside.
So, to answer you question, you can just rely on the existing mtl typeclasses to take care of this. All of the primitive operations like getRandom are polymorphic over their monad, so they will work with whatever stack you end up with in the end. Just wrap all your transformers into a type of your own (Game), and you're all set.
This sounds like a good use-case for the operational package. It lets you define a monad as a set of operations and their return types using a GADT and you can then easily build an interpreter function like the runGame function you suggested. For example:
{-# LANGUAGE GADTs #-}
import Control.Monad.Operational
import System.Random
data Player = Player {
_hand :: [Card],
_deck :: [Card],
_board :: [Card]}
data Coin = Head | Tail
data CardOp a where
FlipCoin :: CardOp Coin
ShuffleDeck :: CardOp ()
type CardAction = Program CardOp
flipCoin :: CardAction Coin
flipCoin = singleton FlipCoin
shuffleDeck :: CardAction ()
shuffleDeck = singleton ShuffleDeck
erk :: CardAction ()
erk = do
coin <- flipCoin
case coin of
Head -> shuffleDeck
Tail -> return ()
runGame :: RandomGen g => g -> CardAction a -> Player -> Player
runGame = step where
step g action player = case view action of
Return _ -> player
FlipCoin :>>= continue ->
let (heads, g') = random g
coin = if heads then Head else Tail
in step g' (continue coin) player
...etc...
However, you might also want to consider just describing all your card actions as a simple ADT without do-syntax. I.e.
data CardAction
= CoinFlip CardAction CardAction
| ShuffleDeck
| DoNothing
erk :: CardAction
erk = CoinFlip ShuffleDeck DoNothing
You can easily write an interpreter for the ADT and as a bonus you can also e.g. generate the card's rule text automatically.

Haskell - Lenses, use of 'to' function

I have the following code. I'd like to be able to modify the active player's life when given a game state. I came up with an activePlayer lens, but when I try and use it in combination with the -= operator I receive the following error:
> over (activePlayer.life) (+1) initialState
<interactive>:2:7:
No instance for (Contravariant Mutator)
arising from a use of `activePlayer'
Possible fix:
add an instance declaration for (Contravariant Mutator)
In the first argument of `(.)', namely `activePlayer'
In the first argument of `over', namely `(activePlayer . life)'
In the expression: over (activePlayer . life) (+ 1) initialState``
and the code in question:
{-# LANGUAGE TemplateHaskell #-}
module Scratch where
import Control.Lens
import Control.Monad.Trans.Class
import Control.Monad.Trans.State
import Data.Sequence (Seq)
import qualified Data.Sequence as S
data Game = Game
{ _players :: (Int, Seq Player) -- active player, list of players
, _winners :: Seq Player
}
deriving (Show)
initialState = Game
{ _players = (0, S.fromList [player1, player2])
, _winners = S.empty
}
data Player = Player
{ _life :: Integer
}
deriving (Show, Eq)
player1 = Player
{ _life = 10
}
player2 = Player
{ _life = 10
}
makeLenses ''Game
makeLenses ''Player
activePlayer
:: (Functor f, Contravariant f) =>
(Player -> f Player) -> Game -> f Game
activePlayer = players.to (\(i, ps) -> S.index ps i)
Each player takes their turn in order. I need to keep track of all the players at once as well as which is currently active, which is the reason for how I structured that, although I am open to different structures since I probably don't have the right one yet.
When you compose various items in the lens library with (.) they may lose capabilities according to a kind of subtyping (see below). In this case, you've composed a Lens (players) with a Getter (to f for some function f) and thus the combination is just a Getter while over acts on lenses that can both get and set.
activePlayer should form a valid lens, though, so you can just write it manually as a getter/setter pair. I'm writing it partially below under the assumption that the index can never be invalid.
activePlayer :: Lens' Game Player
activePlayer = lens get set
where
get :: Game -> Player
get (Game { _players = (index, seq) }) = Seq.index seq index
set :: Game -> Player -> Game
set g#(Game { _players = (index, seq) }) player =
g { _players = (index, Seq.update index player seq) }
To better understand the subtyping that's occurring in the lens library we can use the Big Lattice Diagram from Hackage
Whenever you combine two lens types with (.) you end up with their first common descendent in that chart. So if you combine Lens and Prism you can see that their arrows converge on Traversal. If you combine Lens and Getter (of which to f is) then you get a Getter since Getter is a direct descendent of Lens.

Haskell polymorphic functions with records and class types

this post is the following of this one.
I'm realizing a simple battle system as toy project, the typical system you can find in games like Final Fantasy et simila. I've solved the notorious "Namespace Pollution" problem with a class type + custom instances. For example:
type HitPoints = Integer
type ManaPoints = Integer
data Status = Sleep | Poison | .. --Omitted
data Element = Fire | ... --Omitted
class Targetable a where
name :: a -> String
level :: a -> Int
hp :: a -> HitPoints
mp :: a -> ManaPoints
status :: a -> Maybe [Status]
data Monster = Monster{monsterName :: String,
monsterLevel :: Int,
monsterHp :: HitPoints,
monsterMp :: ManaPoints,
monsterElemType :: Maybe Element,
monsterStatus :: Maybe [Status]} deriving (Eq, Read)
instance Targetable Monster where
name = monsterName
level = monsterLevel
hp = monsterHp
mp = monsterMp
status = monsterStatus
data Player = Player{playerName :: String,
playerLevel :: Int,
playerHp :: HitPoints,
playerMp :: ManaPoints,
playerStatus :: Maybe [Status]} deriving (Show, Read)
instance Targetable Player where
name = playerName
level = playerLevel
hp = playerHp
mp = playerMp
status = playerStatus
Now the problem: I have a spell type, and a spell can deal damage or inflict a status (like Poison, Sleep, Confusion, etc):
--Essentially the result of a spell cast
data SpellEffect = Damage HitPoints ManaPoints
| Inflict [Status] deriving (Show)
--Essentially a magic
data Spell = Spell{spellName :: String,
spellCost :: Integer,
spellElem :: Maybe Element,
spellEffect :: SpellEffect} deriving (Show)
--For example
fire = Spell "Fire" 20 (Just Fire) (Damage 100 0)
frogSong = Spell "Frog Song" 30 Nothing (Inflict [Frog, Sleep])
As suggested in the linked topic, I've created a generic "cast" function like this:
--cast function
cast :: (Targetable t) => Spell -> t -> t
cast s t =
case spellEffect s of
Damage hp mana -> t
Inflict statList -> t
As you can see the return type is t, here showed just for consistency. I want be able to return a new targetable (i.e. a Monster or a Player) with some field value altered (for example a new Monster with less hp, or with a new status). The problem is that i can't just to the following:
--cast function
cast :: (Targetable t) => Spell -> t -> t
cast s t =
case spellEffect s of
Damage hp' mana' -> t {hp = hp', mana = mana'}
Inflict statList -> t {status = statList}
because hp, mana and status "are not valid record selector". The problem is that I don't know a priori if t will be a monster or a player, and I don't want to specify "monsterHp" or "playerHp", I want to write a pretty generic function.
I know that Haskell Records are clumsy and not much extensibile...
Any idea?
Bye and happy coding,
Alfredo
Personally, I think hammar is on the right track with pointing out the similarities between Player and Monster. I agree you don't want to make them the same, but consider this: Take the type class you have here...
class Targetable a where
name :: a -> String
level :: a -> Int
hp :: a -> HitPoints
mp :: a -> ManaPoints
status :: a -> Maybe [Status]
...and replace it with a data type:
data Targetable = Targetable { name :: String
, level :: Int
, hp :: HitPoints
, mp :: ManaPoints
, status :: Maybe [Status]
} deriving (Eq, Read, Show)
Then factor out the common fields from Player and Monster:
data Monster = Monster { monsterTarget :: Targetable
, monsterElemType :: Maybe Element,
} deriving (Eq, Read, Show)
data Player = Player { playerTarget :: Targetable } deriving (Eq, Read, Show)
Depending on what you do with these, it might make more sense to turn it inside-out instead:
data Targetable a = Targetable { target :: a
, name :: String
-- &c...
}
...and then have Targetable Player and Targetable Monster. The advantage here is that any functions that work with either can take things of type Targetable a--just like functions that would have taken any instance of the Targetable class.
Not only is this approach nearly identical to what you have already, it's also a lot less code, and keeps the types simpler (by not having class constraints everywhere). In fact, the Targetable type above is roughly what GHC creates behind the scenes for the type class.
The biggest downside to this approach is that it makes accessing fields clumsier--either way, some things end up being two layers deep, and extending this approach to more complicated types can nest them deeper still. A lot of what makes this awkward is the fact that field accessors aren't "first class" in the language--you can't pass them around like functions, abstract over them, or anything like that. The most popular solution is to use "lenses", which another answer mentioned already. I've typically used the fclabels package for this, so that's my recommendation.
The factored-out types I suggest, combined with strategic use of lenses, should give you something that's simpler to use than the type class approach, and doesn't pollute the namespace the way having lots of record types does.
I can suggest three possible solutions.
1) Your types are very OO-like, but Haskell can also express "sum" types with parameters:
data Unit = UMon Monster | UPlay Player
cast :: Spell -> Unit -> Unit
cast s t =
case spellEffect s of
Damage hp' mana' -> case t of
UMon m -> UMon (m { monsterHp = monsterHp m - hp', monsterMana = undefined})
UPluy p -> UPlay (p { playerHp = playerHp p - hp'})
Inflict statList -> undefined
Thing that are similar in OO-design often become "sum" types with parameters in Haskell.
2) You can do what Carston suggests and add all your methods to type classes.
3) You can change your read-only methods in Targetable to be "lenses" that expose both getting and setting. See the stack overflow discussion. If your type class returned lenses then it would make your spell damage possible to apply.
Why don't you just include functions like
InflicteDamage :: a -> Int -> a
AddStatus :: a -> Status -> a
into your type-class?

What does "exists" mean in Haskell type system?

I'm struggling to understand the exists keyword in relation to Haskell type system. As far as I know, there is no such keyword in Haskell by default, but:
There are extensions which add them, in declarations like these data Accum a = exists s. MkAccum s (a -> s -> s) (s -> a)
I've seen a paper about them, and (if I recall correctly) it stated that exists keyword is unnecessary for type system since it can be generalized by forall
But I can't even understand what exists means.
When I say, forall a . a -> Int, it means (in my understanding, the incorrect one, I guess) "for every (type) a, there is a function of a type a -> Int":
myF1 :: forall a . a -> Int
myF1 _ = 123
-- okay, that function (`a -> Int`) does exist for any `a`
-- because we have just defined it
When I say exists a . a -> Int, what can it even mean? "There is at least one type a for which there is a function of a type a -> Int"? Why one would write a statement like that? What the purpose? Semantics? Compiler behavior?
myF2 :: exists a . a -> Int
myF2 _ = 123
-- okay, there is at least one type `a` for which there is such function
-- because, in fact, we have just defined it for any type
-- and there is at least one type...
-- so these two lines are equivalent to the two lines above
Please note it's not intended to be a real code which can compile, just an example of what I'm imagining then I hear about these quantifiers.
P.S. I'm not exactly a total newbie in Haskell (maybe like a second grader), but my Math foundations of these things are lacking.
A use of existential types that I've run into is with my code for mediating a game of Clue.
My mediation code sort of acts like a dealer. It doesn't care what the types of the players are - all it cares about is that all the players implement the hooks given in the Player typeclass.
class Player p m where
-- deal them in to a particular game
dealIn :: TotalPlayers -> PlayerPosition -> [Card] -> StateT p m ()
-- let them know what another player does
notify :: Event -> StateT p m ()
-- ask them to make a suggestion
suggest :: StateT p m (Maybe Scenario)
-- ask them to make an accusation
accuse :: StateT p m (Maybe Scenario)
-- ask them to reveal a card to invalidate a suggestion
reveal :: (PlayerPosition, Scenario) -> StateT p m Card
Now, the dealer could keep a list of players of type Player p m => [p], but that would constrict
all the players to be of the same type.
That's overly constrictive. What if I want to have different kinds of players, each implemented
differently, and run them against each other?
So I use ExistentialTypes to create a wrapper for players:
-- wrapper for storing a player within a given monad
data WpPlayer m = forall p. Player p m => WpPlayer p
Now I can easily keep a heterogenous list of players. The dealer can still easily interact with the
players using the interface specified by the Player typeclass.
Consider the type of the constructor WpPlayer.
WpPlayer :: forall p. Player p m => p -> WpPlayer m
Other than the forall at the front, this is pretty standard haskell. For all types
p that satisfy the contract Player p m, the constructor WpPlayer maps a value of type p
to a value of type WpPlayer m.
The interesting bit comes with a deconstructor:
unWpPlayer (WpPlayer p) = p
What's the type of unWpPlayer? Does this work?
unWpPlayer :: forall p. Player p m => WpPlayer m -> p
No, not really. A bunch of different types p could satisfy the Player p m contract
with a particular type m. And we gave the WpPlayer constructor a particular
type p, so it should return that same type. So we can't use forall.
All we can really say is that there exists some type p, which satisfies the Player p m contract
with the type m.
unWpPlayer :: exists p. Player p m => WpPlayer m -> p
When I say, forall a . a -> Int, it
means (in my understanding, the
incorrect one, I guess) "for every
(type) a, there is a function of a
type a -> Int":
Close, but not quite. It means "for every type a, this function can be considered to have type a -> Int". So a can be specialized to any type of the caller's choosing.
In the "exists" case, we have: "there is some (specific, but unknown) type a such that this function has the type a -> Int". So a must be a specific type, but the caller doesn't know what.
Note that this means that this particular type (exists a. a -> Int) isn't all that interesting - there's no useful way to call that function except to pass a "bottom" value such as undefined or let x = x in x. A more useful signature might be exists a. Foo a => Int -> a. It says that the function returns a specific type a, but you don't get to know what type. But you do know that it is an instance of Foo - so you can do something useful with it despite not knowing its "true" type.
It means precisely "there exists a type a for which I can provide values of the following types in my constructor." Note that this is different from saying "the value of a is Int in my constructor"; in the latter case, I know what the type is, and I could use my own function that takes Ints as arguments to do something else to the values in the data type.
Thus, from the pragmatic perspective, existential types allow you to hide the underlying type in a data structure, forcing the programmer to only use the operations you have defined on it. It represents encapsulation.
It is for this reason that the following type isn't very useful:
data Useless = exists s. Useless s
Because there is nothing I can do to the value (not quite true; I could seq it); I know nothing about its type.
UHC implements the exists keyword. Here's an example from its documentation
x2 :: exists a . (a, a -> Int)
x2 = (3 :: Int, id)
xapp :: (exists b . (b,b -> a)) -> a
xapp (v,f) = f v
x2app = xapp x2
And another:
mkx :: Bool -> exists a . (a, a -> Int)
mkx b = if b then x2 else ('a',ord)
y1 = mkx True -- y1 :: (C_3_225_0_0,C_3_225_0_0 -> Int)
y2 = mkx False -- y2 :: (C_3_245_0_0,C_3_245_0_0 -> Int)
mixy = let (v1,f1) = y1
(v2,f2) = y2
in f1 v2
"mixy causes a type error. However, we can use y1 and y2 perfectly well:"
main :: IO ()
main = do putStrLn (show (xapp y1))
putStrLn (show (xapp y2))
ezyang also blogged well about this: http://blog.ezyang.com/2010/10/existential-type-curry/

Resources