Data member of some class - haskell

Simplified problem
Given
class Foo f where
frobnicate :: f -> Float
how could I allow any instance of Foo in
data Bar = Bar { <here> }
?
Actual problem
Given
-- Typically lightweight geometric objects, e.g. spheres
class Shape s where
intersect :: (RealFrac t, Floating t, Ord t, Shape s)
=> Ray t -> s t -> Maybe (DifferentialGeometry t)
and
-- Primitives contain higher level informations, like material properties
class Primitive p where
intersect :: (RealFrac t, Floating t, Ord t, Primitive p)
=> Ray t -> p t -> Maybe (Intersection t)
Note the only difference in the signatures of Primitive.intersect and Shape.intersect lies in the return type.
Now I would like to add a wrapper which basically transforms any Shape into a Primitive.
I would think it works roughly like this:
data ShapeWrapperPrimitive t = ShapeWrapperPrimitive {
shape :: (Shape s) => s t
}
or in other words, I would like to add an arbitrary shape member, which is of the Shape class.
However, this gives me Illegal polymorphic or qualified type.

I'm not sure if your simplified problem is really a simplification of the actual problem. The answer to the simplified problem is:
If the only thing you can do with an unknown type that is an instance of class Foo is to turn it into a Float, then you can just as well store the Float.
So you'd use
data Bar = Bar Float
However, if I understand your actual problem correctly, then you want to wrap a type that is an instance of class Shape and thereby turn it into an instance of class Primitive. For this, I'd define
newtype ShapeWrapperPrimitive s t = ShapeWrapperPrimitive (s t)
and then say
instance Shape s => Primitive (ShapeWrapperPrimitive s) where
intersect = ... -- fill in definition here

This isn't an answer to the question you asked, but it may be helpful. If you're creating a list with both Shapes and Primitives, then you need a wrapper type, as described by thoferon. But if you're not, then maybe you don't really need a wrapper type.
You said "Note the only difference in the signatures of Primitive.intersect and Shape.intersect lies in the return type." You can represent that relationship using type families, as shown below. This gives you a type family called Thing. The result type of intersect can be different for each type that is an instance of Thing.
{-# LANGUAGE TypeFamilies, TypeSynonymInstances #-}
class Thing t where
type Result t
intersect :: Ray t -> s t -> Maybe (Result t)
-- Made-up type definitions just to get things to compile
data Shape s t = Shape s t
data Primitive p t = Primitive p t
type Ray t = (Double, t)
type DifferentialGeometry t = [t]
type Intersection t = [t]
-- Typically lightweight geometric objects, e.g. spheres
instance Thing (Shape s t) where
type Result (Shape s t) = DifferentialGeometry t
intersect a b = undefined
-- Primitives contain higher level informations, like material properties
instance Thing (Primitive p t) where
type Result (Primitive p t) = Intersection t
intersect a b = undefined

I can see two solutions to this kind of problems :
1) Use the language extension ExistentialQuantification. So you can write :
data Blah = forall a. Num a => Blah a
2) Move the constraint to your functions, like
data Blah a = Blah a
f :: (Num a) => Blah a -> a
f = undefined
or your instances :
instance (Num a) => Foo (Blah a) where
-- ...

Even though I accepted another answer, I'll post this for future visitors.
My problem was more or less a what could be considered a typo. At some point, I had
23: data ShapeWrapperPrimitive s t = ShapeWrapperPrimitive s t
24:
25: instance (Shape s) => Primitive (ShapeWrapperPrimitive s) where
26: intersect _ _ = Nothing
--- >> line 25: Expecting one more argument to `s'
which let me to a path of confusion and torment. Notice how it points me to line 25. The accepted answer uncovered my mistake: Instead of
data ShapeWrapperPrimitive s t = ShapeWrapperPrimitive s t
I was in need of
data ShapeWrapperPrimitive s t = ShapeWrapperPrimitive (s t)
The first would have added an s and a t as a members, whereas I really wanted an s t; adding the parens solved my problem.

Related

Is there a way to inform Haskell to unwrap a type class inside a sum type

I will briefly explain my chain of thought before the example so that if any of it does not make sense we are able to fix that as well.
Suppose that for each type constructor of my data declaration (a sum of product types) there is one parameter that has an instance to a given type class. In my head, that means that I would be able to explain to GHC/Haskell how to get to that specific type so that my type would end up behaving like an instance of that type class.
For example:
data Vector
-- The class type I talked about
class Transformable a where
setPosition' :: Vector -> a -> IO ()
setOrigin' :: Vector -> a -> IO ()
setAngle' :: Float -> a -> IO ()
-- ... this goes a long way
data TCircleShape
data TSquareShape
data TTriangleShape
data TConvexShape
-- Large sum type that defines different types of Shape
data Shape = Circle Float TCircleShape
| Square Float String TSquareShape
| Triangle Float TTriangleShape
| Convex [Vector] Float TConvexShape
-- ...
-- Almost all of the the Shape constructors have at least one
-- parameter that has an instance of the Transformable typeclass:
instance Transformable TCircleShape
instance Transformable TSquareShape
instance Transformable TTriangleShape
instance Transformable TConvexShape
-- What I would like to write then is:
runOnTransformable :: Transformable a => (a -> IO ()) -> Shape -> IO ()
runOnTransformable = undefined -- (???)
-- What I am doing right now is simply expanding Shape manually:
setShapePosition :: Vector -> Shape -> IO ()
setShapePosition v (Circle _ ptr) = setPosition' v ptr
setShapePosition v (Square _ _ ptr) = setPosition' v ptr
-- and so on...
setShapeAngle' :: Float -> Shape -> IO ()
setShapeAngle' f (Circle _ ptr) = setAngle' f ptr
setShapeAngle' f (Convex _ _ ptr) = setAngle' f ptr
-- and so on...
There is a clear pattern in my eyes and I would like to have some way of abstracting this unwrapping somehow.
One might try to have an instance for the data type itself:
instance Transformable Shape where
setPosition' v (Circle _ ptr) = setPosition' v ptr
-- [...]
setAngle' f (Convex _ _ ptr) = setAngle' f ptr
-- [...]
The downside is that I would have to 'reimplement' all the methods by manually unwrapping the type classes again, except it is in an instance declaration. Right?
Coming back to my question: Is there a way to inform Haskell how to unwrap and act upon a type class from a sum type?
I have a really thin familiarity with Lens and none with TemplateHaskell, however, if using said features would be a probable solution, by all means, go for it.
Your runOnTransformable function is not possible to write as specified, because its type signature is wrong.
runOnTransformable :: Transformable a => (a -> IO ()) -> Shape -> IO ()
means that for any a, which the caller of runOnTransformable chooses, they can provide you a function taking that specific a, and you will call that function with an a of the right type, which you will produce somehow from the Shape object you have. Now, that is clearly not possible, because they may pass you a function of type TSquareShape -> IO () but a Shape which has no TSquareShape in it. Worse, GHC will worry that someone may define instance Transformable Integer where {...}, and you need to be able to handle that case too even though your Shape type doesn't have any way to guess what Integer to give to this function.
You don't want to say that your function works for any Transformable a => a, but rather that the caller's function must work for any Transformable a => a, so that it will be willing to accept whatever value happens to live in your Shape type. You will need the RankNTypes extension to enable you to write the correct signature:
runOnTransformable :: (forall a. Transformable a => a -> IO ()) -> Shape -> IO ()
Sadly, after you've done this I still don't know an automated way to implement this function for all of the various constructors of Shape. I think something ought to be possible with Generic or Data, or Template Haskell or something, but that's beyond my knowledge. Hopefully what I've written here is enough to get you moving in the right direction.
Warning: Speculative answer, proceed with care.
Here is an alternative approach that uses data families. A data family is, in essence, a type-level function which introduces brand new types for their results. In this case, the data families ShapeData and TShape are used to produce the types of the Shape fields.
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
data Circle'
data Square'
data family ShapeData s
newtype instance ShapeData Circle' = DCircle Float
deriving (Eq, Show)
data instance ShapeData Square' = DSquare Float String
deriving (Eq, Show)
data family TShape s
data instance TShape Circle' = TCircle
data instance TShape Square' = TSquare
class Transformable a where
setAngle' :: Float -> a -> IO ()
instance Transformable (TShape Circle') where
setAngle' _ _ = putStrLn ("Setting a circle angle is a no-op")
instance Transformable (TShape Square') where
setAngle' x _ = putStrLn ("Setting the square angle to " ++ show x)
data Shape a = Shape (ShapeData a) (TShape a)
instance Transformable (TShape a) => Transformable (Shape a) where
setAngle' x (Shape _ t) = setAngle' x t
Additional remarks:
In addition to data families, there are also type families, which result in preexisting types rather than newly introduced ones. Since here we would have to define TCircleShape, TSquareShape etc. separately, we might as well do that through a data family.
I replaced your Shape constructors with empty data types, which are then used to fill in the gaps of a now parametric Shape type. One significant difference in relation to your sum type approach is that the set of possible shapes is now open to extension. If you needed it to be closed, I believe it would be possible by reaching to something even fancier: singletons -- you would define a sum type data Shape' = Circle' | Square', then use e.g. the singletons machinery to promote the constructors to type level and using the resulting types as parameters to Shape.

Type class definition with functions depending on an additional type

Still new to Haskell, I have hit a wall with the following:
I am trying to define some type classes to generalize a bunch of functions that use gaussian elimination to solve linear systems of equations.
Given a linear system
M x = k
the type a of the elements m(i,j) \elem M can be different from the type b of x and k. To be able to solve the system, a should be an instance of Num and b should have multiplication/addition operators with b, like in the following:
class MixedRing b where
(.+.) :: b -> b -> b
(.*.) :: (Num a) => b -> a -> b
(./.) :: (Num a) => b -> a -> b
Now, even in the most trivial implementation of these operators, I'll get Could not deduce a ~ Int. a is a rigid type variable errors (Let's forget about ./. which requires Fractional)
data Wrap = W { get :: Int }
instance MixedRing Wrap where
(.+.) w1 w2 = W $ (get w1) + (get w2)
(.*.) w s = W $ ((get w) * s)
I have read several tutorials on type classes but I can find no pointer to what actually goes wrong.
Let us have a look at the type of the implementation that you would have to provide for (.*.) to make Wrap an instance of MixedRing. Substituting Wrap for b in the type of the method yields
(.*.) :: Num a => Wrap -> a -> Wrap
As Wrap is isomorphic to Int and to not have to think about wrapping and unwrapping with Wrap and get, let us reduce our goal to finding an implementation of
(.*.) :: Num a => Int -> a -> Int
(You see that this doesn't make the challenge any easier or harder, don't you?)
Now, observe that such an implementation will need to be able to operate on all types a that happen to be in the type class Num. (This is what a type variable in such a type denotes: universal quantification.) Note: this is not the same (actually, it's the opposite) of saying that your implementation can itself choose what a to operate on); yet that is what you seem to suggest in your question: that your implementation should be allowed to pick Int as a choice for a.
Now, as you want to implement this particular (.*.) in terms of the (*) for values of type Int, we need something of the form
n .*. s = n * f s
with
f :: Num a => a -> Int
I cannot think of a function that converts from an arbitary Num-type a to Int in a meaningful way. I'd therefore say that there is no meaningful way to make Int (and, hence, Wrap) an instance of MixedRing; that is, not such that the instance behaves as you would probably expect it to do.
How about something like:
class (Num a) => MixedRing a b where
(.+.) :: b -> b -> b
(.*.) :: b -> a -> b
(./.) :: b -> a -> b
You'll need the MultiParamTypeClasses extension.
By the way, it seems to me that the mathematical structure you're trying to model is really module, not a ring. With the type variables given above, one says that b is an a-module.
Your implementation is not polymorphic enough.
The rule is, if you write a in the class definition, you can't use a concrete type in the instance. Because the instance must conform to the class and the class promised to accept any a that is Num.
To put it differently: Exactly the class variable is it that must be instantiated with a concrete type in an instance definition.
Have you tried:
data Wrap a = W { get :: a }
Note that once Wrap a is an instance, you can still use it with functions that accept only Wrap Int.

Haskell get type of algebraic parameter

I have a type
class IntegerAsType a where
value :: a -> Integer
data T5
instance IntegerAsType T5 where value _ = 5
newtype (IntegerAsType q) => Zq q = Zq Integer deriving (Eq)
newtype (Num a, IntegerAsType n) => PolyRing a n = PolyRing [a]
I'm trying to make a nice "show" for the PolyRing type. In particular, I want the "show" to print out the type 'a'. Is there a function that returns the type of an algebraic parameter (a 'show' for types)?
The other way I'm trying to do it is using pattern matching, but I'm running into problems with built-in types and the algebraic type.
I want a different result for each of Integer, Int and Zq q.
(toy example:)
test :: (Num a, IntegerAsType q) => a -> a
(Int x) = x+1
(Integer x) = x+2
(Zq x) = x+3
There are at least two different problems here.
1) Int and Integer are not data constructors for the 'Int' and 'Integer' types. Are there data constructors for these types/how do I pattern match with them?
2) Although not shown in my code, Zq IS an instance of Num. The problem I'm getting is:
Ambiguous constraint `IntegerAsType q'
At least one of the forall'd type variables mentioned by the constraint
must be reachable from the type after the '=>'
In the type signature for `test':
test :: (Num a, IntegerAsType q) => a -> a
I kind of see why it is complaining, but I don't know how to get around that.
Thanks
EDIT:
A better example of what I'm trying to do with the test function:
test :: (Num a) => a -> a
test (Integer x) = x+2
test (Int x) = x+1
test (Zq x) = x
Even if we ignore the fact that I can't construct Integers and Ints this way (still want to know how!) this 'test' doesn't compile because:
Could not deduce (a ~ Zq t0) from the context (Num a)
My next try at this function was with the type signature:
test :: (Num a, IntegerAsType q) => a -> a
which leads to the new error
Ambiguous constraint `IntegerAsType q'
At least one of the forall'd type variables mentioned by the constraint
must be reachable from the type after the '=>'
I hope that makes my question a little clearer....
I'm not sure what you're driving at with that test function, but you can do something like this if you like:
{-# LANGUAGE ScopedTypeVariables #-}
class NamedType a where
name :: a -> String
instance NamedType Int where
name _ = "Int"
instance NamedType Integer where
name _ = "Integer"
instance NamedType q => NamedType (Zq q) where
name _ = "Zq (" ++ name (undefined :: q) ++ ")"
I would not be doing my Stack Overflow duty if I did not follow up this answer with a warning: what you are asking for is very, very strange. You are probably doing something in a very unidiomatic way, and will be fighting the language the whole way. I strongly recommend that your next question be a much broader design question, so that we can help guide you to a more idiomatic solution.
Edit
There is another half to your question, namely, how to write a test function that "pattern matches" on the input to check whether it's an Int, an Integer, a Zq type, etc. You provide this suggestive code snippet:
test :: (Num a) => a -> a
test (Integer x) = x+2
test (Int x) = x+1
test (Zq x) = x
There are a couple of things to clear up here.
Haskell has three levels of objects: the value level, the type level, and the kind level. Some examples of things at the value level include "Hello, world!", 42, the function \a -> a, or fix (\xs -> 0:1:zipWith (+) xs (tail xs)). Some examples of things at the type level include Bool, Int, Maybe, Maybe Int, and Monad m => m (). Some examples of things at the kind level include * and (* -> *) -> *.
The levels are in order; value level objects are classified by type level objects, and type level objects are classified by kind level objects. We write the classification relationship using ::, so for example, 32 :: Int or "Hello, world!" :: [Char]. (The kind level isn't too interesting for this discussion, but * classifies types, and arrow kinds classify type constructors. For example, Int :: * and [Int] :: *, but [] :: * -> *.)
Now, one of the most basic properties of Haskell is that each level is completely isolated. You will never see a string like "Hello, world!" in a type; similarly, value-level objects don't pass around or operate on types. Moreover, there are separate namespaces for values and types. Take the example of Maybe:
data Maybe a = Nothing | Just a
This declaration creates a new name Maybe :: * -> * at the type level, and two new names Nothing :: Maybe a and Just :: a -> Maybe a at the value level. One common pattern is to use the same name for a type constructor and for its value constructor, if there's only one; for example, you might see
newtype Wrapped a = Wrapped a
which declares a new name Wrapped :: * -> * at the type level, and simultaneously declares a distinct name Wrapped :: a -> Wrapped a at the value level. Some particularly common (and confusing examples) include (), which is both a value-level object (of type ()) and a type-level object (of kind *), and [], which is both a value-level object (of type [a]) and a type-level object (of kind * -> *). Note that the fact that the value-level and type-level objects happen to be spelled the same in your source is just a coincidence! If you wanted to confuse your readers, you could perfectly well write
newtype Huey a = Louie a
newtype Louie a = Dewey a
newtype Dewey a = Huey a
where none of these three declarations are related to each other at all!
Now, we can finally tackle what goes wrong with test above: Integer and Int are not value constructors, so they can't be used in patterns. Remember -- the value level and type level are isolated, so you can't put type names in value definitions! By now, you might wish you had written test' instead:
test' :: Num a => a -> a
test' (x :: Integer) = x + 2
test' (x :: Int) = x + 1
test' (Zq x :: Zq a) = x
...but alas, it doesn't quite work like that. Value-level things aren't allowed to depend on type-level things. What you can do is to write separate functions at each of the Int, Integer, and Zq a types:
testInteger :: Integer -> Integer
testInteger x = x + 2
testInt :: Int -> Int
testInt x = x + 1
testZq :: Num a => Zq a -> Zq a
testZq (Zq x) = Zq x
Then we can call the appropriate one of these functions when we want to do a test. Since we're in a statically-typed language, exactly one of these functions is going to be applicable to any particular variable.
Now, it's a bit onerous to remember to call the right function, so Haskell offers a slight convenience: you can let the compiler choose one of these functions for you at compile time. This mechanism is the big idea behind classes. It looks like this:
class Testable a where test :: a -> a
instance Testable Integer where test = testInteger
instance Testable Int where test = testInt
instance Num a => Testable (Zq a) where test = testZq
Now, it looks like there's a single function called test which can handle any of Int, Integer, or numeric Zq's -- but in fact there are three functions, and the compiler is transparently choosing one for you. And that's an important insight. The type of test:
test :: Testable a => a -> a
...looks at first blush like it is a function that takes a value that could be any Testable type. But in fact, it's a function that can be specialized to any Testable type -- and then only takes values of that type! This difference explains yet another reason the original test function didn't work. You can't have multiple patterns with variables at different types, because the function only ever works on a single type at a time.
The ideas behind the classes NamedType and Testable above can be generalized a bit; if you do, you get the Typeable class suggested by hammar above.
I think now I've rambled more than enough, and likely confused more things than I've clarified, but leave me a comment saying which parts were unclear, and I'll do my best.
Is there a function that returns the type of an algebraic parameter (a 'show' for types)?
I think Data.Typeable may be what you're looking for.
Prelude> :m + Data.Typeable
Prelude Data.Typeable> typeOf (1 :: Int)
Int
Prelude Data.Typeable> typeOf (1 :: Integer)
Integer
Note that this will not work on any type, just those which have a Typeable instance.
Using the extension DeriveDataTypeable, you can have the compiler automatically derive these for your own types:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
data Foo = Bar
deriving Typeable
*Main> typeOf Bar
Main.Foo
I didn't quite get what you're trying to do in the second half of your question, but hopefully this should be of some help.

Is there a type 'Any' in haskell?

Say, I want to define a record Attribute like this:
data Attribute = Attribute {name :: String, value :: Any}
This is not valid haskell code of course. But is there a type 'Any' which basically say any type will do? Or is to use type variable the only way?
data Attribute a = Attribute {name :: String, value :: a}
Generally speaking, Any types aren't very useful. Consider: If you make a polymorphic list that can hold anything, what can you do with the types in the list? The answer, of course, is nothing - you have no guarantee that there is any operation common to these elements.
What one will typically do is either:
Use GADTs to make a list that can contain elements of a specific typeclass, as in:
data FooWrap where
FooWrap :: Foo a => a -> FooWrap
type FooList = [FooWrap]
With this approach, you don't know the concrete type of the elements, but you know they can be manipulated using elements of the Foo typeclass.
Create a type to switch between specific concrete types contained in the list:
data FooElem = ElemFoo Foo | ElemBar Bar
type FooList = [FooElem]
This can be combined with approach 1 to create a list that can hold elements that are of one of a fixed set of typeclasses.
In some cases, it can be helpful to build a list of manipulation functions:
type FooList = [Int -> IO ()]
This is useful for things like event notification systems. At the time of adding an element to the list, you bind it up in a function that performs whatever manipulation you'll later want to do.
Use Data.Dynamic (not recommended!) as a cheat. However, this provides no guarantee that a specific element can be manipulated at all, and so the above approaches should be preferred.
Adding to bdonlan's answer: Instead of GADTs, you can also use existential types:
{-# LANGUAGE ExistentialQuantification #-}
class Foo a where
foo :: a -> a
data AnyFoo = forall a. Foo a => AnyFoo a
instance Foo AnyFoo where
foo (AnyFoo a) = AnyFoo $ foo a
mapFoo :: [AnyFoo] -> [AnyFoo]
mapFoo = map foo
This is basically equivalent to bdonlan's GADT solution, but doesn't impose the choice of data structure on you - you can use a Map instead of a list, for example:
import qualified Data.Map as M
mFoo :: M.Map String AnyFoo
mFoo = M.fromList [("a", AnyFoo SomeFoo), ("b", AnyFoo SomeBar)]
The data AnyFoo = forall a. Foo a => AnyFoo a bit can also be written in GADT notation as:
data AnyFoo where
AnyFoo :: Foo a => a -> AnyFoo
There is the type Dynamic from Data.Dynamic which can hold anything (well, anything Typeable). But that is rarely the right way to do it. What is the problem that you are trying to solve?
This sounds like a pretty basic question, so I'm going to give an even more basic answer than anybody else. Here's what is almost always the right solution:
data Attribute a = Attribute { name :: String, value :: a }
Then, if you want an attribute that wraps an Int, that attribute would have type Attribute Int, or an attribute that wraps a Bool would have type Attribute Bool, etc. You can create these attributes with values of any type; for example, we can write
testAttr = Attribute { name = "this is only a test", value = Node 3 [] }
to create a value of type Attribute (Tree Int).
If your data needs to be eventually a specific type, You could use Convertible with GADTs. Because as consumer, you are only interested in a the datatype you need to consume.
{-# LANGUAGE GADTs #-}
import Data.Convertible
data Conv b where
Conv :: a -> (a -> b) -> Conv b
Chain :: Conv b -> (b -> c) -> Conv c
unconv :: (Conv b) -> b
unconv (Conv a f) = f a
unconv (Chain c f) = f $ unconv c
conv :: Convertible a b => a -> Conv b
conv a = (Conv a convert)
totype :: Convertible b c => Conv b -> Conv c
totype a = Chain a convert
It is not very difficult to derive functor, comonad and monad instances for this. I can post them if you are interested.
Daniel Wagner response is the right one: almost in 90% of cases using a polymorphic type is all that you need.
All the other responses are useful for the remaining 10% of cases, but if you have still no good knowledge of polymorphism as to ask this question, it will be extremely complicated to understand GADTs or Existential Types...
My advice is "keep it as simple as possible".

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