Existential type in higher order function - haskell

I've got a function whose job is to compute some optimal value of type a wrt some value function of type a -> v
type OptiF a v = (a -> v) -> a
Then I have a container that wants to store such a function together with another function which uses the values values:
data Container a = forall v. (Ord v) => Cons (OptiF a v) (a -> Int)
The idea is that whoever implements a function of type OptiF a v should not be bothered with the details of v except that it's an instance of Ord.
So I've written a function which takes such a value function and a container. Using the OptiF a v it should compute the optimal value wrt val and plug it in the container's result function:
optimize :: (forall v. (Ord v) => a -> v) -> Container a -> Int
optimize val (Cons opti result) = result (opti val)
So far so good, but I can't call optimize, because
callOptimize :: Int
callOptimize = optimize val cont
where val = (*3)
opti val' = if val' 1 > val' 0 then 100 else -100
cont = Cons opti (*2)
does not compile:
Could not deduce (v ~ Int)
from the context (Ord v)
bound by a type expected by the context: Ord v => Int -> v
at bla.hs:12:16-32
`v' is a rigid type variable bound by
a type expected by the context: Ord v => Int -> v at bla.hs:12:16
Expected type: Int
Actual type: Int
Expected type: Int -> v
Actual type: Int -> Int
In the first argument of `optimize', namely `val'
In the expression: optimize val cont
where line 12:16-32 is optimize val cont.
Am I misunderstanding existential types in this case? Does the forall v in the declaration of optimize mean that optimize may expect from a -> v whatever v it wants? Or does it mean that optimize may expect nothing from a -> v except that Ord v?
What I want is that the OptiF a v is not fixed for any v, because I want to plug in some a -> v later on. The only constraint I'd like to impose is Ord v. Is it even possible to express something like that using existential types (or whatever)?
I managed to achieve that with an additional typeclass which provides an optimize function with a similar signature to OptiF a v, but that looks much uglier to me than using higher order functions.

This is something that's easy to get wrong.
What you have in the signature of optimize is not an existential, but a universal.
...since existentials are somewhat outdated anyway, let's rewrite your data to GADT form, which makes the point clearer as the syntax is essentially the same as for polymorphic functions:
data Container a where
(:/->) :: Ord v => -- come on, you can't call this `Cons`!
OptiF a v -> (a->Int) -> Container a
Observe that the Ord constraint (which implies that here's the forall v...) stands outside of the type-variable–parameterised function signature, i.e. v is a parameter we can dictate from the outside when we want to construct a Container value. In other words,
For all v in Ord there exists the constructor (:/->) :: OptiF a v -> (a->Int) -> Container a
which is what gives rise to the name "existential type". Again, this is analog to an ordinary polymorphic function.
On the other hand, in the signature
optimize :: (forall v. (Ord v) => a -> v) -> Container a -> Int
you have a forall inside the signature term itself, which means that what concrete type v may take on will be determined by the callee, optimize, internally – all we have control over from the outside is that it be in Ord. Nothing "existential" about that, which is why this signature won't actually compile with XExistentialQuantification or XGADTs alone:
<interactive>:37:26:
Illegal symbol '.' in type
Perhaps you intended -XRankNTypes or similar flag
to enable explicit-forall syntax: forall <tvs>. <type>
val = (*3) obviously doesn't fulfill (forall v. (Ord v) => a -> v), it actually requires a Num instance which not all Ords have. Indeed, optimize shouldn't need the rank2 type: it should work for any Ord-type v the caller might give to it.
optimize :: Ord v => (a -> v) -> Container a -> Int
in which case your implementation doesn't work anymore, though: since (:/->) is really an existential constructor, it needs to contain only any OptiF function, for some unknown type v1. So the caller of optimize has the freedom to choose the opti-function for any particular such type, and the function to be optimised for any possibly other fixed type – that can't work!
The solution that you want is this: Container shouldn't be existential, either! The opti-function should work for any type which is in Ord, not just for one particular type. Well, as a GADT this looks about the same as the universally-quantified signature you originally had for optimize:
data Container a where
(:/->) :: (forall v. Ord v => OptiF a v) -> (a->Int) -> Container a
With that now, optimize works
optimize :: Ord v => (a -> v) -> Container a -> Int
optimize val (opti :/-> result) = result (opti val)
and can be used as you wanted
callOptimize :: Int
callOptimize = optimize val cont
where val = (*3)
opti val' = if val' 1 > val' 0 then 100 else -100
cont = opti :/-> (*2)

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 generic constraint kinds

I can quite validly write a type like this in Haskell:
(t ~ (a, b)) => t
Which in a roundabout way says that t is some pair.
But lets say I want to do this:
type family MyConstraint t :: Constraint
data PairConstraintParam
type instance MyConstraint PairConstraintParam = ...
(t ~ MyConstraint PairConstraintParam) => t
What can I place after the type instance MyConstraint PairConstraintParam =
I tried (a,b) but GHC complained a and b were not on the RHS. It didn't seem to like foralls either.
This may seem like a silly example, there's potentially different constraints for different instances of a class, so hence this roundabout scheme. As the constraints affect and depend on parameters to a method in a class, I can't just place them in the instance head.
I think the equality constraint here doesn't really make sense in that form. ~ should have a sort like k -> k -> Constraint, so t in that context would need to have kind Constraint on the left side, while on the right side you need to end with *...
However, if I have understood the problem correctly, you need to have existential type for a and b; so maybe this is what you want:
data PairConstraintParam
data ExistentialPair :: * where
Exists :: (a, b) -> ExistentialPair
type family MyConstraint (p :: *) (t :: *) :: Constraint where
MyConstraint PairConstraintParam t = t ~ ExistentialPair
test :: (MyConstraint PairConstraintParam t) => t
test = Exists (1, "hi")
Meaning that "there exist a, b, such that t ~ (a, b)" (up to isomorphism). Of course, you would want to add some more constraints to actually do something useful.
Another variant I can think of is the following:
data ConstraintVariant = PairConstraint
class IsPair p where
instance IsPair (a, b)
type family ConstrainedBy (c :: ConstraintVariant) :: * -> Constraint where
ConstrainedBy PairConstraint = IsPair
data Thing c t where
Thing :: (c t) => t -> Thing c t
test2 :: Thing (ConstrainedBy PairConstraint) (Int, String)
test2 = Thing (1, "hi")
Which lets you recover both the constraint and the underlying type.

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

How to state that a type variable in a newtype statement is of a type that belongs to some type class?

Suppose that I have this newtype:
newtype SomeType a = SomeType { foo :: OtherType a }
I want to ensure that a is showable (belongs to the type class Show x).
How do I ensure that? (Is it even possible?)
Bonus points: am I using the terminology correctly?
It is possible with the DatatypeContexts extension, but it is strongly discouraged:
newtype Show a => SomeType a = SomeType { foo :: Maybe a }
It is recommended to put the constraint on the functions that use SomeType or use GADTs. See the answers to these questions for more information.
Alternative for deprecated -XDatatypeContext?
DatatypeContexts Deprecated in Latest GHC: Why?
Basically, it doesn't add anything useful and it makes you have to put constraints where they wouldn't otherwise be necessary.
To demonstrate #David's answer in a small example, imagine you're implementing another incarnation of a balanced binary tree. Of course keys must be Ordered, so you add a constraint to the type declaration:
data Ord k => Tree k v = Tip | Bin k v (Tree k v) (Tree k v)
Now this constraint infects every other signature everywhere you're using this type, even when you don't really need to order keys. It wouldn't probably be a bad thing (after all, you'll need to order them at least somewhere – otherwise, you aren't really using this Tree) and it definitely doesn't break the code, but still makes it less readable, adds noise and distracts from important things.
empty :: Ord k => Tree k v
singleton :: Ord k => k -> v -> Tree k v
find :: Ord k => (v -> Bool) -> Tree k v -> Maybe v
instance Ord k => Functor (Tree k)
In all of these signatures the constraint could be omitted without any problems.

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.

Resources