The type variable ‘a0’ is ambiguous - haskell

I don't understand why the following code won't compile:
{-# LANGUAGE GADTs, ScopedTypeVariables #-}
data A = A
class C a where
c :: a -> Bool
instance C A where
c _ = True
data D a where
D :: C a => D a
toBool :: D a -> Bool
toBool D = c (undefined::a)
Here is the error message:
Could not deduce (C a0) arising from a use of ‘c’
from the context (C a)
bound by a pattern with constructor
D :: forall a. C a => D a,
in an equation for ‘toBool’
at test.hs:15:8
The type variable ‘a0’ is ambiguous
Note: there is a potential instance available:
instance C A -- Defined at test.hs:8:10
In the expression: c (undefined :: a)
In an equation for ‘toBool’: toBool D = c (undefined :: a)
Can someone explain what's going on ?
                                       

The type variables introduced in a top-level type declaration are not the same as those introduced inside the body of the function. Another way of saying this is the nested type declarations introduce "fresh" variables. Another another way to say this is to put explicit foralls in your code where Haskell automatically introduces them, silently:
toBool :: forall a . D a -> Bool
toBool D = c (undefined :: forall a . a) -- another forall here?
What you really intended was
toBool :: forall a . D a -> Bool
toBool D = c (undefined :: a) -- capture `a` from prior scope
and, you're in luck. It turns out that almost everyone needs this kind of functionality from time to time so a very common Haskell extension exists called ScopedTypeVariables. The following code ought to compile
{-# LANGUAGE ScopedTypeVariables #-}
toBool :: forall a . D a -> Bool
toBool D = c (undefined :: a)
Note that in order to invoke ScopedTypeVariables you must now manually introduce the foralls that you want to be treated specially. Without that manual forall Haskell will automatically introduce them at all the same locations it normally does.

Related

Is it possible to write an alias for coerce?

Let's say for the purposes of this question I want to make an alias of coerce. I start with the obvious
import Data.Coerce
q = coerce
a bit surprisingly this gives rise an error:
coerce.hs:3:5: error:
• Couldn't match representation of type ‘a0’ with that of ‘b0’
arising from a use of ‘coerce’
• In the expression: coerce
In an equation for ‘q’: q = coerce
• Relevant bindings include q :: a0 -> b0 (bound at coerce.hs:4:1)
|
4 | q = coerce
| ^^^^^^
This error is quite opaque so I slapped the type signature1 of coerce onto q:
{-# Language RankNTypes #-}
{-# Language KindSignatures #-}
{-# Language PolyKinds #-}
import Data.Coerce
import GHC.Exts
q :: forall (k :: RuntimeRep) (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b
q = coerce
But this gives rise to the error:
coerce.hs:8:5: error:
Cannot use function with levity-polymorphic arguments:
coerce :: a -> b
Levity-polymorphic arguments: a :: TYPE k
|
8 | q = coerce
| ^^^^^^
This error is not very helpful. It informs me there is an issue with levity polymorphism and that is about it.
What is really quite curious to me is that when I make q bottom:
{-# Language RankNTypes #-}
{-# Language KindSignatures #-}
{-# Language PolyKinds #-}
import Data.Coerce
import GHC.Exts
q :: forall (k :: RuntimeRep) (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b
q = q
The error goes away and the code compiles fine.
I'm left unsure whether such an alias is possible, or what even the issue with the alias is.
Is such an alias possible where q maintains the type of coerce? What issue is the compiler running into with my code?
1: As pointed out by the comments this type signature only has levity polymorphism in since base-4.13 or ghc 8.8. For the purposes of this question we want the levity polymorphism.
#dfeuer's answer covers a workaround, but I think issue #17670 explains why this is happening. Because coerce is a primop, it must be fully saturated, so any use is implicitly eta-expanded. When you write:
q = coerce
you're really writing:
q = \x -> coerce x
The initial error message you get is actually a result of the monomorphism restriction. If you write either:
q x = coerce x
or add the NoMonomorphismRestriction extension, the program is accepted. Unfortunately, the resulting q isn't levity polymorphic. It's instantiated with lifted types.
If try to force the issue by adding an appropriate polymorphic type signature:
q :: forall (k :: RuntimeRep) (a :: TYPE k) (b :: TYPE k). Coercible a b => a -> b
q = coerce
then bleeding edge versions of GHC (e.g., "8.11" built from source last month) give an elaborated error message:
BadCoerce.hs:11:5: error:
Cannot use function with levity-polymorphic arguments:
coerce :: a -> b
(Note that levity-polymorphic primops such as 'coerce' and unboxed tuples
are eta-expanded internally because they must occur fully saturated.
Use -fprint-typechecker-elaboration to display the full expression.)
Levity-polymorphic arguments: a :: TYPE k
Ultimately, you're running up against the prohibition that no variable (in this case an implicit variable introduced to eta-expand coerce) is permitted to be levity polymorphic. The reason q = q works is that there's no eta expansion and so no variable involved. Try q x = q x and it will fail with "a levity-polymorphic type is not allowed here" error message.
It doesn't look like this is possible, but you can get really close. Note: it may well be possible to shorten this.
blop
:: forall (k :: RuntimeRep) (a :: TYPE k) (b :: TYPE k) q r.
Coercible a b
=> q :~: (a -> a)
-> r :~: (a -> b)
-> Coercion q r
blop Refl Refl = Coercion
bloverce
:: forall (k :: RuntimeRep) (a :: TYPE k) (b :: TYPE k) q r.
Coercible a b
=> q :~: (a -> a)
-> r :~: (a -> b)
-> q -> r
bloverce qaa rab = case blop qaa rab of Coercion -> coerce
gloerce
:: forall (r :: RuntimeRep).
(forall (x :: TYPE r). x -> x) -> Coe r
gloerce kid = Coe (bloverce Refl Refl (kid :: a -> a) :: forall (a :: TYPE r) (b :: TYPE r). Coercible a b => a -> b)
newtype Coe (r :: RuntimeRep) = Coe (forall (a :: TYPE r) (b :: TYPE r). Coercible a b => a -> b)
As long as you can provide the polymorphic identity function for a certain runtime representation, you can use gloerce to get its coerce.
Of course, this is all fairly silly in practice: in the rare cases when you need a representation-polymorphic coercion function, you can just use coerce directly.

How do I change this to say the body types should equal the parameter types?

I am trying to use a typeclass to pass a dictionary into a function where the values of the dictionary are uniquely specified by the types of two types parameters of the function.
When I compile this code, I get the error message in the comment.
How do I modify this code to avoid this ambiguity? I would like the a and b types in the body to be the same as the ones in the formal parameters.
{-# LANGUAGE MultiParamTypeClasses#-}
class C a b where
a :: a
b :: b
f :: C a b => a -> b
f a = b
-- $ runhaskell toy2.hs
-- toy2.hs:8:7:
-- Could not deduce (C a0 b) arising from a use of ‘b’
-- from the context (C a b)
-- bound by the type signature for f :: C a b => a -> b
-- at toy2.hs:7:6-20
-- The type variable ‘a0’ is ambiguous
-- Relevant bindings include f :: a -> b (bound at toy2.hs:8:1)
-- In the expression: b
-- In an equation for ‘f’: f a = b
Then usage would be like
instance C String Double where
a = "foo"
b = 42.0
and
f "bar" = 42.0
To illustrate the problem, consider these two instances:
instance Char Double where
a = 'x'
b = 42.0
instance Char Int where
a = 'x'
b = 17
Now f 'c' needs to equal b, but which b? There are two instances of C that could work.
One solution is to use a functional dependency to enforce that the type of b depends on the type of a:
class C a b | b -> a where
a :: a
b :: b
Just note that you may run into some type inference issues that require explicit annotations.
Using explicit type arguments. I'm not convinced this is a good approach,
though.
{-# LANGUAGE AllowAmbiguousTypes, TypeApplications,
ScopedTypeVariables, MultiParamTypeClasses #-}
class C a b where
getA :: a
getB :: b
foo :: forall a b. C a b => a -> b
foo _ = getB # a
instance C Int Char where
getA = 3
getB = 'a'
test :: Char
test = foo # Int # Char 23
Are you sure you don't have any functional dependency between a and b? Otherwise, you have to always disambiguate with explicit type arguments.

Haskell - constructing a type that uses existential quantification

In the code below I have defined a data type F using existential quantification. I would like values of type F to hold functions that accept a single argument and produce, say, an Int as the result. The argument needs to implement a type class which I've called C, but left empty for now.
This is my first attempt at existential types. I am clearly doing something wrong as I don't seem to be able to create values of type F.
{-# LANGUAGE ExistentialQuantification #-}
class C a where
data F = forall a. C a => F (a->Int)
makeF :: F
makeF = F $ const 1
How can I fix this compile error?
No instance for (C a0) arising from a use of `F'
In the expression: F
In the expression: F $ const 1
In an equation for `makeF': makeF = F $ const 1
The problem is that const 1 has type forall a . C a => a -> Int. When you pass that to F we lose the opportunity to ever talk about the type a again excepting that it is an element of type C.
Unfortunately, we've never determined what a must be!
In particular, GHC handles existentials like this by passing in the dictionary for the typeclass C corresponding to whatever type actually ends up in the existential. Since we never provided GHC enough information to find that dictionary it gives us a type error.
So to fix this we must instantiate C somewhere
instance C Int
and then pass a function which determines that the forgotten type a actually is an instance of C
let x = F (const 1 :: Int -> Int)
If you rewrite your F definition as below it will work:
{-# LANGUAGE RankNTypes #-}
class C a where
data F = F (forall a. C a => a -> Int)
makeF :: F
makeF = F $ const 1
I'm trying to understand why myself:
Your original type says "there exists a which is instance of C, and we have function a -> Int".
So to construct existential type, we have to state which a we have:
{-# LANGUAGE ExistentialQuantification #-}
class C a where
data F = forall a. C a => F (a -> Int)
-- Implement class for Unit
instance C () where
makeF :: F
makeF = F $ (const 1 :: () -> Int)
These aren't exactly equivalent definitions:
data G = forall a . C a => G {
value :: a -- is a value! could be e.g. `1` or `()`
toInt :: a -> Int, -- Might be `id`
}
data G' = G' {
value' :: C a => a -- will be something for every type of instance `C`
toInt' :: C a => a -> Int, -- again, by parametericity uses only `C` stuff
}

ScopedTypeVariables between a type class and its instance

The Haskell wiki on ScopedTypeVariables does not describe how the scope of a type variable is handled between a type class and its instance.
The following compiles
{-# LANGUAGE ScopedTypeVariables #-}
class A a where
f :: forall b. a -> b -> (a,b)
instance A Int where
f a b = (idb a, ida b)
where idb :: b -> b
idb = id
ida :: a -> a
ida = id
while the following does not (as expected: Couldn't match expected type ‘a’ with actual type ‘b’)
g :: forall a b. a -> b -> (a,b)
g a b = (idb a, b)
where idb :: b -> b
idb = id
Since the wiki is silent, how was ScopedTypeVariables supposed to work with type classes? Is this a bug, a misfeature, or by design? The wiki mentions some work-arounds that are Haskell98 and they seem to be compatible with using type classes (and thus superior).
EDIT:
As mentioned in a comment, InstanceSigs makes it possible to re-introduce the signature from the class and thus bring the type variables into scope. But this seems very awkward compared to the Haskell98 alternative:
data D
instance A D where
f a b = (idb a, b)
where idb x = asTypeOf b x -- gives the correct error message
{-# LANGUAGE InstanceSigs #-}
data E
instance A E where
-- Complicated way to bring the class signature into scope..?
f :: forall b. E -> b -> (E, b)
f a b = (idb a, b)
where idb :: b -> b
idb = id
Doesn't it make more sense that the scope from the class declaration is re-used in the instance declaration to make ScopedTypeVariables work nicely with type classes?
In the instance definition you're not using scoped type variables. There you just provide annotations for idb and ida in the where block, and both are generalized to the same type, namely forall a. a -> a (modulo renaming of type variables), so they both work on any type.
Also, in the instance definition you have A Int, so there isn't any variable you could refer to.
Generally, type variables in an instance head are visible by default in the instance implementation if we have ScopedTypeVariables, and otherwise not visible. Also, note that when visible they can be shadowed by other scoped type variables (like any other scoped type var).
Examples:
class A a where
f :: a -> b -> (a,b)
instance A a where
f x y = (x :: a, y) -- an error without ScopedTypeVariables, fine with it.
instance A a where
f x y = (x , y) where
foo :: forall a. a -> a
foo _ = x -- an error, because we shadowed the instance "a" with the forall "a"

Polyvariadic Functions in Haskell

After reading this article on writing polyvariadic functions in Haskell, I tried to write some of my own.
At first I thought I'd try to generalize it - so I could have a function that returned variadic functions by collapsing arguments as given.
{-# OPTIONS -fglasgow-exts #-}
module Collapse where
class Collapse a r | r -> a where
collapse :: (a -> a -> a) -> a -> r
instance Collapse a a where
collapse _ = id
instance (Collapse a r) => Collapse a (a -> r) where
collapse f a a' = collapse f (f a a')
However, the compiler didn't like that:
Collapse.hs:5:9:
Functional dependencies conflict between instance declarations:
instance Collapse a a -- Defined at Collapse.hs:5:9-20
instance (Collapse a r) => Collapse a (a -> r)
-- Defined at Collapse.hs:7:9-43
If I went back and added a wrapper type for the final result, however, it worked:
module Collapse where
class Collapse a r | r -> a where
collapse :: (a -> a -> a) -> a -> r
data C a = C a
instance Collapse a (C a) where
collapse _ = C . id
instance (Collapse a r) => Collapse a (a -> r) where
collapse f a a' = collapse f (f a a')
sum :: (Num a, Collapse a r) => a -> r
sum = collapse (+)
Once I made this change, it compiled fine, and I could use the collapse function in ghci.
ghci> let C s = Collapse.sum 1 2 3 in s
6
I'm not sure why the wrapper type is required for the final result. If anyone could explain that, I'd highly appreciate it. I can see that the compiler's telling me that it's some issue with the functional dependencies, but I don't really grok the proper use of fundeps yet.
Later, I tried to take a different tack, and try and define a variadic function generator for functions that took a list and returned a value. I had to do the same container trick, and also allow UndecidableInstances.
{-# OPTIONS -fglasgow-exts #-}
{-# LANGUAGE UndecidableInstances #-}
module Variadic where
class Variadic a b r | r -> a, r -> b where
variadic :: ([a] -> b) -> r
data V a = V a
instance Variadic a b (V b) where
variadic f = V $ f []
instance (Variadic a b r) => Variadic a b (a -> r) where
variadic f a = variadic (f . (a:))
list :: Variadic a [a] r => r
list = variadic . id
foldl :: (Variadic b a r) => (a -> b -> a) -> a -> r
foldl f a = variadic (Prelude.foldl f a)
Without allowing UndecidableInstances the compiler complained that my instance declarations were illegal:
Variadic.hs:7:0:
Illegal instance declaration for `Variadic a b (V b)'
(the Coverage Condition fails for one of the functional dependencies;
Use -XUndecidableInstances to permit this)
In the instance declaration for `Variadic a b (V b)'
Variadic.hs:9:0:
Illegal instance declaration for `Variadic a b (a -> r)'
(the Coverage Condition fails for one of the functional dependencies;
Use -XUndecidableInstances to permit this)
In the instance declaration for `Variadic a b (a -> r)'
However, once it compiled, I could successfully use it in ghci:
ghci> let V l = Variadic.list 1 2 3 in l
[1,2,3]
ghci> let vall p = Variadic.foldl (\b a -> b && (p a)) True
ghci> :t vall
vall :: (Variadic b Bool r) => (b -> Bool) -> r
ghci> let V b = vall (>0) 1 2 3 in b
True
I guess what I'm looking for is an explanation of why the container type for the final value is necessary, as well as why all the various functional dependencies are necessary.
Also, this seemed odd:
ghci> let vsum = Variadic.foldl (+) 0
<interactive>:1:10:
Ambiguous type variables `a', `r' in the constraint:
`Variadic a a r'
arising from a use of `Variadic.foldl' at <interactive>:1:10-29
Probable fix: add a type signature that fixes these type variable(s)
<interactive>:1:10:
Ambiguous type variable `a'in the constraint:
`Num a' arising from the literal `0' at <interactive>:1:29
Probable fix: add a type signature that fixes these type variable(s)
ghci> let vsum' = Variadic.foldl (+)
ghci> :t vsum'
(Num a, Variadic a a r) => t -> a -> r
ghci> :t vsum' 0
(Num a, Variadic a a r) => a -> r
ghci> let V s = vsum' 0 1 2 3 in s
6
I'm guessing that's fallout from allowing UndecidableInstances, but I don't know, and I'd like to better understand what's going on.
The idea behind functional dependencies is that in a declaration like
class Collapse a r | r -> a where
...
the r -> a bit says that a is uniquely determined by r. So, you can't have instance Collapse (a -> r) (a -> r) and instance Collapse a (a -> r). Note that instance Collapse (a -> r) (a -> r) follows from instance Collapse a a for the complete picture.
In other words, your code is trying to establish instance Collapse t t (the type variable's name is of course unimportant) and instance Collapse a (a -> r). If you substitute (a -> r) for t in the first instance declaration, you get instance Collapse (a -> r) (a -> r). Now this is the only instance of Collapse with the second type parameter equal to (a -> r) that you can have, because the class declaration says that the first type parameter is to be deducible from the second. Yet next you try to establish instance a (a -> r), which would add another instance of Collapse with the second type parameter being (a -> r). Thus, GHC complains.
If you're still experimenting with this, here's an example of constructing a polyvariadic function from a function taking a list, without requiring either a wrapper type or undecidable instances:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
class Variadic a b r | r -> a where
variadic :: ([a] -> b) -> r
instance Variadic a b (a -> b) where
variadic f x = f [x]
instance (Variadic a b (a -> r)) => Variadic a b (a -> a -> r) where
variadic f x y = variadic (f . (x:)) y
vList :: (Variadic a [a] r) => r
vList = variadic id
vFoldl :: (Variadic b a r) => (a -> b -> a) -> a -> r
vFoldl f z = variadic (foldl f z)
vConcat :: (Variadic [a] [a] r) => r
vConcat = vFoldl (++) []
main = do
putStrLn $ vConcat "abc" "def" "ghi" "jkl"
putStrLn $ vList 'x' 'y' 'z'
if vFoldl (&&) True True True True then putStrLn "Yes" else putStrLn "No"
if vFoldl (&&) True True False True then putStrLn "Yes" else putStrLn "No"
The downsides to this approach are that the type checker must be able to infer the type of the result (or you have to annotate it), and that it fails badly on polymorphic numeric constants; the reasons for both problems are discussed in the article you mentioned. Don't know if you'll find that helpful, but I was tinkering with polyvariadic functions earlier and remembered this question.
Michał Marczyk is absolutely correct about the fundeps and instance matching issue, and the wrapper type seems like an easy fix. On the other hand, if you're already reading Oleg's site, you might prefer to go deeper down the rabbit hole and try writing an instance for "any type that isn't a function".
As far as UndecidableInstances goes, the coverage condition is described here; it should be obvious why your instances fail it. Note that the word "undecidable" here means undecidable in roughly the same sense as in "the Halting Problem is undecidable"--that is to say, you're telling GHC to recklessly attempt to resolve code that could send it into an infinite loop based only on your assertion that it's okay. It's fun for hacking neat ideas, but consenting to be a human first-pass type-checker for GHC is a burden I personally find wearying.

Resources