Ambiguous type variables for dependent class constraints - haskell

I'm writing a new authentication system for the Snap web framework, because the built-in one isn't modular enough, and it has some features that are redundant/"dead weight" for my application. This problem isn't related to Snap at all, though.
While doing so, I hit a problem with ambiguous type constraints. In the following code, it seems obvious to me that the type of back can only be the type variable b in the functions type, yet GHC complains that the type is ambiguous.
How can I change the following code such that the type of back is b, without using e.g. ScopedTypeVariables (because the problem is with the constraint, not with having too general types)? Is there a functional dependency that is needed somewhere?
Relevant type classes:
data AuthSnaplet b u =
AuthSnaplet
{ _backend :: b
, _activeUser :: Maybe u
}
-- data-lens-template:Data.Lens.Template.makeLens
-- data-lens:Data.Lens.Common.Lens
-- generates: backend :: Lens (AuthSnaplet b u) b
makeLens ''AuthSnaplet
-- Some encrypted password
newtype Password =
Password
{ passwordData :: ByteString
}
-- data-default:Data.Default.Default
class Default u => AuthUser u where
userLogin :: Lens u Text
userPassword :: Lens u Password
class AuthUser u => AuthBackend b u where
save :: MonadIO m => b -> u -> m u
lookupByLogin :: MonadIO m => b -> Text -> m (Maybe u)
destroy :: MonadIO m => b -> u -> m ()
-- snap:Snap.Snaplet.Snaplet
class AuthBackend b u => HasAuth s b u where
authSnaplet :: Lens s (Snaplet (AuthSnaplet b u))
The code that fails:
-- snap:Snap.Snaplet.with :: Lens v (Snaplet v') -> m b v' a -> m b v a
-- data-lens-fd:Data.Lens.access :: MonadState a m => Lens a b -> m b
loginUser :: HasAuth s b u
=> Text -> Text -> Handler a s (Either AuthFailure u)
loginUser uname passwd = with authSnaplet $ do
back <- access backend
maybeUser <- lookupByLogin back uname -- !!! type of back is ambiguous !!!
-- ... For simplicity's sake, let's say the function ends like this:
return . Right . fromJust $ maybeUser
Full error:
src/Snap/Snaplet/Authentication.hs:105:31:
Ambiguous type variables `b0', `u0' in the constraint:
(HasAuth s b0 u0) arising from a use of `authSnaplet'
Probable fix: add a type signature that fixes these type variable(s)
In the first argument of `with', namely `authSnaplet'
In the expression: with authSnaplet
In the expression:
with authSnaplet
$ do { back <- access backend;
maybeUser <- lookupByLogin back uname;
... }
src/Snap/Snaplet/Authentication.hs:107:16:
Ambiguous type variable `b0' in the constraint:
(AuthBackend b0 u) arising from a use of `lookupByLogin'
Probable fix: add a type signature that fixes these type variable(s)
In a stmt of a 'do' expression:
maybeUser <- lookupByLogin back uname
In the second argument of `($)', namely
`do { back <- access backend;
maybeUser <- lookupByLogin back uname;
... }'
In the expression:
with authSnaplet
$ do { back <- access backend;
maybeUser <- lookupByLogin back uname;
... }

I would venture to guess that the root of your problem is in the expression with authSnaplet. Here's why:
∀x. x ⊢ :t with authSnaplet
with authSnaplet
:: AuthUser u => m b (AuthSnaplet b1 u) a -> m b v a
Don't mind the context, I filled in some bogus instances just to load stuff in GHCi. Note the type variables here--lots of ambiguity, and at least two that I expect you intend to be the same type. The easiest way to handle this is probably to create a small, auxiliary function with a type signature that narrows things down a bit, e.g.:
withAuthSnaplet :: (AuthUser u)
=> Handler a (AuthSnaplet b u) (Either AuthFailure u)
-> Handler a s (Either AuthFailure u)
withAuthSnaplet = with authSnaplet
Again, pardon the nonsense, I don't actually have Snap installed at the moment, which makes things awkward. Introducing this function, and using it in place of with authSnaplet in loginUser, allows the code to type check for me. You may need to tweak things a bit to handle your actual instance constraints.
Edit: If the above technique doesn't let you nail down b by some means, and assuming that the types really are intended to be as generic as they're written, then b is impossibly ambiguous and there's no way around it.
Using with authSnaplet eliminates b entirely from the actual type, but leaves it polymorphic with a class constraint on it. This is the same ambiguity that an expression like show . read has, with instance-dependent behavior but no way to pick one.
To avoid this, you have roughly three choices:
Retain the ambiguous type explicitly, so that b is found somewhere in the actual type of loginUser, not just the context. This may be undesirable for other reasons in the context of your application.
Remove the polymorphism, by only applying with authSnaplet to suitably monomorphic values. If the types are known in advance, there's no room for ambiguity. This potentially means giving up some polymorphism in your handlers, but by breaking things apart you can limit the monomorphism to only code that cares what b is.
Make the class constraints themselves unambiguous. If the three type parameters to HasAuth are, in practice, interdependent to some degree such that there will only be one valid instance for any s and u, then a functional dependency from the others to b would be completely appropriate.

Related

How do you apply function constraints in instance methods in Haskell?

I'm learning how to use typeclasses in Haskell.
Consider the following implementation of a typeclass T with a type constrained class function f.
class T t where
f :: (Eq u) => t -> u
data T_Impl = T_Impl_Bool Bool | T_Impl_Int Int | T_Impl_Float Float
instance T T_Impl where
f (T_Impl_Bool x) = x
f (T_Impl_Int x) = x
f (T_Impl_Float x) = x
When I load this into GHCI 7.10.2, I get the following error:
Couldn't match expected type ‘u’ with actual type ‘Float’
‘u’ is a rigid type variable bound by
the type signature for f :: Eq u => T_Impl -> u
at generics.hs:6:5
Relevant bindings include
f :: T_Impl -> u (bound at generics.hs:6:5)
In the expression: x
In an equation for ‘f’: f (T_Impl_Float x) = x
What am I doing/understanding wrong? It seems reasonable to me that one would want to specialize a typeclass in an instance by providing an accompaning data constructor and function implementation. The part
Couldn't match expected type 'u' with actual type 'Float'
is especially confusing. Why does u not match Float if u only has the constraint that it must qualify as an Eq type (Floats do that afaik)?
The signature
f :: (Eq u) => t -> u
means that the caller can pick t and u as wanted, with the only burden of ensuring that u is of class Eq (and t of class T -- in class methods there's an implicit T t constraint).
It does not mean that the implementation can choose any u.
So, the caller can use f in any of these ways: (with t in class T)
f :: t -> Bool
f :: t -> Char
f :: t -> Int
...
The compiler is complaining that your implementation is not general enough to cover all these cases.
Couldn't match expected type ‘u’ with actual type ‘Float’
means "You gave me a Float, but you must provide a value of the general type u (where u will be chosen by the caller)"
Chi has already pointed out why your code doesn't compile. But it's not even that typeclasses are the problem; indeed, your example has only one instance, so it might just as well be a normal function rather than a class.
Fundamentally, the problem is that you're trying to do something like
foobar :: Show x => Either Int Bool -> x
foobar (Left x) = x
foobar (Right x) = x
This won't work. It tries to make foobar return a different type depending on the value you feed it at run-time. But in Haskell, all types must be 100% determined at compile-time. So this cannot work.
There are several things you can do, however.
First of all, you can do this:
foo :: Either Int Bool -> String
foo (Left x) = show x
foo (Right x) = show x
In other words, rather than return something showable, actually show it. That means the result type is always String. It means that which version of show gets called will vary at run-time, but that's fine. Code paths can vary at run-time, it's types which cannot.
Another thing you can do is this:
toInt :: Either Int Bool -> Maybe Int
toInt (Left x) = Just x
toInt (Right x) = Nothing
toBool :: Either Int Bool -> Maybe Bool
toBool (Left x) = Nothing
toBool (Right x) = Just x
Again, that works perfectly fine.
There are other things you can do; without knowing why you want this, it's difficult to suggest others.
As a side note, you want to stop thinking about this like it's object oriented programming. It isn't. It requires a new way of thinking. In particular, don't reach for a typeclass unless you really need one. (I realise this particular example may just be a learning exercise to learn about typeclasses of course...)
It's possible to do this:
class Eq u => T t u | t -> u where
f :: t -> u
You need FlexibleContextx+FunctionalDepencencies and MultiParamTypeClasses+FlexibleInstances on call-site. Or to eliminate class and to use data types instead like Gabriel shows here

Using makeLenses, class constraints and type synonyms together

I'm quite new to Haskell and want to use makeLenses from Control.Lens and class constraints together with type synonyms to make my functions types more compact (readable?).
I've tried to come up with a minimal dummy example to demonstrate what I want to achieve and the example serves no other purpose than this.
At the end of this post I've added an example closer to my original problem if you are interested in the context.
Minimal example
As an example, say I define the following data type:
data State a = State { _a :: a
} deriving Show
, for which I also make lenses:
makeLenses ''State
In order to enforce a class constraint on the type parameter a used by the type constructor State I use a smart constructor:
mkState :: (Num a) => a -> State a
mkState n = State {_a = n}
Next, say I have a number of functions with type signatures similar to this:
doStuff :: Num a => State a -> State a
doStuff s = s & a %~ (*2)
This all works as intended, for example:
test = doStuff . mkState $ 5.5 -- results in State {_a = 11.0}
Problem
I've tried to use the following type synonym:
type S = (Num n) => State n -- Requires the RankNTypes extensions
, together with:
{-# LANGUAGE RankNTypes #-}
, in an attempt to simplify the type signature of doStuff:
doStuff :: S -> S
, but this gives the following error:
Couldn't match type `State a0' with `forall n. Num n => State n'
Expected type: a0 -> S
Actual type: a0 -> State a0
In the second argument of `(.)', namely `mkState'
In the expression: doStuff . mkState
In the expression: doStuff . mkState $ 5.5
Failed, modules loaded: none.
Question
My current knowledge of Haskell is not sufficient to understand what causes the above error. I hope someone can explain what causes the error and/or suggest other ways to construct the type synonym or why such a type synonym is not possible.
Background
My original problem looks closer to this:
data State r = State { _time :: Int
, _ready :: r
} deriving Show
makeLenses ''State
data Task = Task { ... }
Here I want to enforce the type of _ready being an instance of the Queue class using the following smart constructor:
mkState :: (Queue q) => Int -> q Task -> State (q Task)
mkState t q = State { _time = t
, _ready = q
}
I also have a number of functions with type signatures similar to this:
updateState :: Queue q => State (q Task) -> Task -> State (q Task)
updateState s x = s & ready %~ (enqueue x) & time %~ (+1)
I would like to use a type synonym S to be able to rewrite the type of such functions as:
updateState :: S -> Task -> S
, but as with the first minimal example I don't know how to define the type synonym S or whether it is possible at all.
Maybe there is no real benefit in trying to simplify the type signatures?
Related reading
I've read the following related questions on SO:
Class constraints for data records
Are type synonyms with typeclass constraints possible?
This might also be related but given my current understanding of Haskell I cannot really understand all of it:
Unifying associated type synonyms with class constraints
Follow-up
It's been a while since I've had the opportunity to do some Haskell. Thanks to #bheklilr I've now managed to introduce a type synonym only to hit the next type error I'm still not able to understand. I've posted the following follow-up question Type synonym causes type error regarding the new type error.
You see that error in particular because of the combination of the . operator and your use of RankNTypes. If you change it from
test = doStuff . mkState $ 5.5
to
test = doStuff $ mkState 5.5
or even
test = doStuff (mkState 5.5)
it will compile. Why is this? Look at the types:
doStuff :: forall n. Num n => State n -> State n
mkState :: Num n => n -> State n
(doStuff) . (mkState) <===> (forall n. Num n => State n -> State n) . (Num n => n -> State n)
Hopefully the parentheses help make it clear here, the n from forall n. Num n ... for doStuff is a different type variable from the Num n => ... for mkState because the scope of the forall only extends to the end of the parentheses. So these functions can't actually compose because the compiler sees them as separate types! There are actually special rules for the $ operator specifically for using the ST monad precisely for this reason, just so you can do runST $ do ....
You may be able to accomplish what you want easier using GADTs, but I don't believe lens' TemplateHaskell will work with GADT types. However, you can write your own pretty easily in this case, so it isn't that big of a deal.
A further explanation:
doStuff . mkState $ 5.5
is very different than
doStuff $ mkState 5.5
In the first one, doStuff says that for all Num types n, its type is State n -> State n, whereas mkState says for some Num type m, its type is m -> State m. These two types are not the same because of the "for all" and "for some" quantifications (hence ExistentialQuantification), since composing them would mean that for some Num m you can produce all Num n.
In the doStuff $ mkState 5.5, you have the equivalent of
(forall n. Num n => State n -> State n) $ (Num m => State m)
Notice that the type after the $ is not a function because mkState 5.5 is fully applied. So this works because for all Num n you can do State n -> State n, and you're providing it some Num m => State m. This works intuitively. Again, the difference here is the composition versus application. You can't compose a function that works on some types with a function that works on all types, but you can pass a value to a function that works on all types ("all types" here meaning forall n. Num n => n).

What is the right way to typecheck dependent lambda abstraction using 'bound'?

I am implementing a simple dependently-typed language, similar to the one described by Lennart Augustsson, while also using bound to manage bindings.
When typechecking a dependent lambda term, such as λt:* . λx:t . x, I need to:
"Enter" the outer lambda binder, by instantiating t to something
Typecheck λx:t . x, yielding ∀x:t . t
Pi-abstract the t, yielding ∀t:* . ∀x:t . t
If lambda was non-dependent, I could get away with instantiating t with its type on step 1, since the type is all I need to know about the variable while typechecking on step 2.
But on step 3 I lack the information to decide which variables to abstract over.
I could introduce a fresh name supply and instantiate t with a Bound.Name.Name containing both the type and a unique name. But I thought that with bound I shouldn't need to generate fresh names.
Is there an alternative solution I'm missing?
We need some kind of context to keep track of the lambda arguments. However, we don't necessarily need to instantiate them, since bound gives us de Bruijn indices, and we can use those indices to index into the context.
Actually using the indices is a bit involved, though, because of the type-level machinery that reflects the size of the current scope (or in other words, the current depth in the expression) through the nesting of Var-s. It necessitates the use of polymorphic recursion or GADTs. It also prevents us from storing the context in a State monad (because the size and thus the type of the context changes as we recurse). I wonder though if we could use an indexed state monad; it'd be a fun experiment. But I digress.
The simplest solution is to represent the context as a function:
type TC a = Either String a -- our checker monad
type Cxt a = a -> TC (Type a) -- the context
The a input is essentially a de Bruijn index, and we look up a type by applying the function to the index. We can define the empty context the following way:
emptyCxt :: Cxt a
emptyCxt = const $ Left "variable not in scope"
And we can extend the context:
consCxt :: Type a -> Cxt a -> Cxt (Var () a)
consCxt ty cxt (B ()) = pure (F <$> ty)
consCxt ty cxt (F a) = (F <$>) <$> cxt a
The size of the context is encoded in the Var nesting. The increase in the size is apparent here in the return type.
Now we can write the type checker. The main point here is that we use fromScope and toScope to get under binders, and we carry along an appropriately extended Cxt (whose type lines up just perfectly).
data Term a
= Var a
| Star -- or alternatively, "Type", or "*"
| Lam (Type a) (Scope () Term a)
| Pi (Type a) (Scope () Term a)
| App (Type a) (Term a)
deriving (Show, Eq, Functor)
-- boilerplate omitted (Monad, Applicative, Eq1, Show1 instances)
-- reduce to normal form
rnf :: Term a -> Term a
rnf = ...
-- Note: IIRC "Simply easy" and Augustsson's post reduces to whnf
-- when type checking. I use here plain normal form, because it
-- simplifies the presentation a bit and it also works fine.
-- We rely on Bound's alpha equality here, and also on the fact
-- that we keep types in normal form, so there's no need for
-- additional reduction.
check :: Eq a => Cxt a -> Type a -> Term a -> TC ()
check cxt want t = do
have <- infer cxt t
when (want /= have) $ Left "type mismatch"
infer :: Eq a => Cxt a -> Term a -> TC (Type a)
infer cxt = \case
Var a -> cxt a
Star -> pure Star -- "Type : Type" system for simplicity
Lam ty t -> do
check cxt Star ty
let ty' = rnf ty
Pi ty' . toScope <$> infer (consCxt ty' cxt) (fromScope t)
Pi ty t -> do
check cxt Star ty
check (consCxt (rnf ty) cxt) Star (fromScope t)
pure Star
App f x ->
infer cxt f >>= \case
Pi ty t -> do
check cxt ty x
pure $ rnf (instantiate1 x t)
_ -> Left "can't apply non-function"
Here's the working code containing the above definitions. I hope I didn't mess it up too badly.

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.

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