Type annotation in a typeclass' default value causes a "could not deduce" type error - haskell

This is a beginner's question, but I cannot recognize any answer to it anywhere.
The following code:
class A a where
foo :: a
class A a => B a where
bar :: a
bar = (foo :: a)
fails to compile in GHC, with the error message:
Could not deduce (A a1) arising from a use of `foo'
from the context (B a)
bound by the class declaration for `B'
...
GHC seems unconvinced that all the a's in the definition of typeclass B are the same. Can anyone please explain what exactly its line of reasoning is?
Removing the type annotation in line 5 avoids the problem of course, but I would still like to understand what is going on here...

You should indeed get rid of the type annotation. Type variables are not scoped in Haskell, so (foo :: a). Is interpreted as "have foo produce a value of type a for any type a", which cannot be done as foo will only produce values of those types a that are in the class A.
Put differently, your declaration of B is equivalent to
class A a => B a where
bar :: a
bar = (foo :: c)
That is, there is no connection between your use of the type variable a and the other uses in the declaration.
Dropping the explicit annotation solves your issue:
class A a => B a where
bar :: a
bar = foo
Now, the compiler can figure out for what type you want to invoke foo, i.e., for the type a that you wrote in the signature of bar and that appears in the head of the class declaration.
The Glasgow Haskell Compiler (GHC) comes with an extension that allows for scoped type variables. With that extension enabled, your fragment is type checked like you originally expected:
{-# LANGUAGE ScopedTypeVariables #-}
class A a where
foo :: a
class A a => B a where
bar :: a
bar = (foo :: a)

Prelude> :set -XScopedTypeVariables
Prelude> :{
Prelude| class A a where
Prelude| foo :: a
Prelude| class A a => B a where
Prelude| bar :: a
Prelude| bar = (foo :: a)
Prelude| :}
Prelude> :t bar
bar :: B a => a
Prelude>
but as dblhelox said, it's not really necessary to use scoped type variables here.

Related

Haskell type inference with GADTs and typeclass constraints on type variables

I defined a custom GADT where the type constructor has a type class constraint on the type variable, like this:
data MyGadt x where
Sample :: Show a => a -> MyGadt a
Now, if I define the following two functions:
foo (Sample a) = show a
bar a = Sample a
GHC infers types for them that are a bit irritating to me.
foo :: MyGadt x -> [Char] doesn't mention the Show constraint for x, while bar :: Show a => a -> MyGadt a does require the constraint to be mentioned explicitly.
I was assuming that I don't have to mention the constraint because it is declared in the GADT definition.
The only thing I can think of being part of the reason is the position of the GADT in the function. I'm not super deep into that but as far as I understand it, MyGadt is in positive position in foo and in negative position in bar.
When do I have to mention the type class constraints explicitly, and when does GHC figure it out itself based on the constraint on the GADTs type constructor?
It's the whole point of using a GADT that you want the constraint to show up in the signature of bar, instead of foo. If you don't want that, then you can use a plain old newtype instead:
newtype MyAdt = Sample a
foo :: Show a => MyAdt a -> String
foo (Sample a) = show a
bar :: a -> MyAdt a
bar = Sample
Having the constraint in neither foo nor bar clearly can't work, because then you would be able to e.g.
showFunction :: (Integer -> Integer) -> String
showFunction = foo . bar

Reify existential instance type parameter

I've got some code like this:
{-# LANGUAGE AllowAmbiguousTypes #-}
module Foo where
import Data.Proxy
class Foo x y
class Bar x y
class Baz x y
where
baz :: Proxy x -> Proxy y -> ()
instance (Foo a v, Bar b v) => Baz a b
where
baz _ _ = ()
instance Foo String String
instance Bar Int String
Now I actually want to use that Baz instance, so I write:
test :: Proxy String -> Proxy Int -> ()
test = baz
But of course there is an ambiguous "existential" v type parameter that I have not yet fixed to String (and there's no fundeps), so I get:
[typecheck] [E] /tmp/foo/src/Main.hs:20:8: error:
• Ambiguous type variable ‘v1’ arising from a use of ‘baz’
prevents the constraint ‘(Foo [Char] v1)’ from being solved.
Probable fix: use a type annotation to specify what ‘k1’,
‘v1’ should be.
These potential instance exist:
one instance involving out-of-scope types
(use -fprint-potential-instances to see them all)
• In the expression: baz
In an equation for ‘test’: test = baz
But how can I actually fix that type variable? I can't see a way to fix it using visible type application, because for example the following doesn't work:
test2 :: Proxy String -> Proxy Int -> ()
test2 = baz #String #Int #String -- is there some variation of this that would work?
I also can't see a way to use an explicit type annotation to fix that type parameter. Have I written an instance that is impossible to actually use?
It is indeed impossible to use that instance. When you call baz, you can supply a and b, but not v. v would have to be determined by some combination of superclass and instance constraints, and it is not.
You should be able to patch this up various places. Try either
instance s ~ String => Foo String s
or
instance s ~ String => Bar Int s
for example.

Why is `succ i` valid where `i :: Num a => a` (and not an `Enum a`)?

This seems to apply to both GHCi and GHC. I'll show an example with GHCi first.
Given i type has been inferred as follows:
Prelude> i = 1
Prelude> :t i
i :: Num p => p
Given that succ is a function defined on Enum:
Prelude> :i Enum
class Enum a where
succ :: a -> a
pred :: a -> a
-- …OMITTED…
and that Num is not a 'subclass' (if I can use that term) of Enum:
class Num a where
(+) :: a -> a -> a
(-) :: a -> a -> a
-- …OMITTED…
why succ i does not return an error?
Prelude> succ i
2 -- works, no error
I would expect :type i to be inferred to something like:
Prelude> i = 1
Prelude> :type i
i :: (Enum p, Num p) => p
(I'm using 'GHC v. 8.6.3')
ADDITION:
After reading #RobinZigmond comment and #AlexeyRomanov answer I have noticed that 1 could be interpreted as one of many types and one of many classes.
Thanks to #AlexeyRomanov answer I understand much more about the defaulting-rules used to decide what type to use for ambiguous expressions.
However I don't feel that Alexey answer addresses exactly my question. My question is about the type of i. It's not about the type of succ i.
It's about the mismatch between succ argument type (an Enum a) and the apparent type of i (a Num a).
I'm now starting to realise that my question must stem from a wrong assumption: 'that once i is inferred to be i :: Num a => a, then i can be nothing else'. Hence I was puzzled to see succ i was evaluated without errors.
GHC also seems to be inferring Enum a in addition to what was explicitly declared.
x :: Num a => a
x = 1
y = succ x -- works
However it is not adding Enum a when the type variable appears as a function:
my_succ :: Num a => a -> a
my_succ z = succ z -- fails compilation
To me it seems that the type constraints attached to a function are stricter to the ones applied to a variable.
GHC is saying my_succ :: forall a. Num a => a -> a and given
forall a doesn't appear in the type-signature of neither i nor x I thought that meant GHC is not going to infer any more classes for my_succ types.
But this seems again wrong: I've checked this idea with the following (first time I type RankNTypes) and apparently GHC still infers Enum a:
{-# LANGUAGE RankNTypes #-}
x :: forall a. Num a => a
x = 1
y = succ x
So it seems that inference rules for functions are stricter than the ones for variables?
Yes, succ i's type is inferred as you expect:
Prelude> :t succ i
succ i :: (Enum a, Num a) => a
This type is ambiguous, but it satisfies the conditions in the defaulting rules for GHCi:
Find all the unsolved constraints. Then:
Find those that are of form (C a) where a is a type variable, and partition those constraints into groups that share a common type variable a.
In this case, there's only one group: (Enum a, Num a).
Keep only the groups in which at least one of the classes is an interactive class (defined below).
This group is kept, because Num is an interactive class.
Now, for each remaining group G, try each type ty from the default-type list in turn; if setting a = ty would allow the constraints in G to be completely solved. If so, default a to ty.
The unit type () and the list type [] are added to the start of the standard list of types which are tried when doing type defaulting.
The default default-type list (sic) is (with the additions from the last clause) default ((), [], Integer, Double).
So when you do Prelude> succ i to actually evaluate this expression (note :t doesn't evaluate the expression it gets), a is set to Integer (first of this list satisfying the constraints), and the result is printed as 2.
You can see it's the reason by changing the default:
Prelude> default (Double)
Prelude> succ 1
2.0
For the updated question:
I'm now starting to realise that my question must stem from a wrong assumption: 'that once i is inferred to be i :: Num a => a, then i can be nothing else'. Hence I was puzzled to see succ i was evaluated without errors.
i can be nothing else (i.e. nothing that doesn't fit this type), but it can be used with less general (more specific) types: Integer, Int. Even with many of them in an expression at once:
Prelude> (i :: Double) ^ (i :: Integer)
1.0
And these uses don't affect the type of i itself: it's already defined and its type fixed. OK so far?
Well, adding constraints also makes the type more specific, so (Num a, Enum a) => a is more specific than (Num a) => a:
Prelude> i :: (Num a, Enum a) => a
1
Because of course any type a that satisfies both constraints in (Num a, Enum a) satisfies just Num a.
However it is not adding Enum a when the type variable appears as a function:
That's because you specified a signature which doesn't allow it to. If you don't give a signature, there's no reason to infer Num constraint. But e.g.
Prelude> f x = succ x + 1
will infer the type with both constraints:
Prelude> :t f
f :: (Num a, Enum a) => a -> a
So it seems that inference rules for functions are stricter than the ones for variables?
It's actually the other way around due to the monomorphism restriction (not in GHCi, by default). You've actually been a bit lucky not to run into it here, but the answer is already long enough. Searching for the term should give you explanations.
GHC is saying my_succ :: forall a. Num a => a -> a and given forall a doesn't appear in the type-signature of neither i nor x.
That's a red herring. I am not sure why it's shown in one case and not the other, but all of them have that forall a behind the scenes:
Haskell type signatures are implicitly quantified. When the language option ExplicitForAll is used, the keyword forall allows us to say exactly what this means. For example:
g :: b -> b
means this:
g :: forall b. (b -> b)
(Also, you just need ExplicitForAll and not RankNTypes to write down forall a. Num a => a.)

Making TypeClass Instance for List

Before getting to my question, let me state my understanding (perhaps incorrect) that a List [] is a higher-kinded type:
ghci> :kind []
[] :: * -> *
I could be mistaken, but, a [] needs a type since it's a List of some type 'T'.
Now to my question.
class Foo a where
bar :: String -> a
Then, I try to create a Foo [String]. My understanding is that the a in Foo a is [String]. So, I'd expect bar to return a [String].
instance Foo [String] where
bar [] = []
bar (x:_) = [x]
However, I get the following compile-time error:
ghci> :l TypeClassExample.hs
[1 of 1] Compiling Main ( TypeClassExample.hs, interpreted )
TypeClassExample.hs:5:10:
Illegal instance declaration for `Foo [String]'
(All instance types must be of the form (T a1 ... an)
where a1 ... an are *distinct type variables*,
and each type variable appears at most once in the instance head.
Use -XFlexibleInstances if you want to disable this.)
In the instance declaration for `Foo [String]'
Failed, modules loaded: none.
I'm hesitant to add this compile-time flag without understanding it.
What is its significance in this simple code?
The Haskell language definition is quite restrictive, and only allows list instances to be of the form
instance ... => Foo [a] where
where in the head a is exactly a type variable a, disallowing e.g. [Int] or [String].
However, you can require GHC to ignore this restriction. Just add at th beginning of your file the following:
{-# LANGUAGE FlexibleInstances #-}
Many, many modern Haskell programs make use of this. Arguably, in the next Haskell definition revision, this GHC feature should be integrated.

Inclusion of typeclasses with default implementation in Haskell

Consider the following definitions:
class Foo a where
foo :: a -> Int
class Bar a where
bar :: a -> [Int]
Now, how do I say "every Foo is also a Bar, with bar defined by default as bar x = [foo x]" in Haskell?
(Whatever I try, the compiler gives me "Illegal instance declaration" or "Constraint is no smaller than the instance head")
Btw, I can define my Foo and Bar classes in some other way, if this would help.
class Foo a where
foo :: a -> Int
-- 'a' belongs to 'Bar' only if it belongs to 'Foo' also
class Foo a => Bar a where
bar :: a -> [Int]
bar x = [foo x] -- yes, you can specify default implementation
instance Foo Char where
foo _ = 0
-- instance with default 'bar' implementation
instance Bar Char
As the automatic definition of a Bar instance through a Foo instance can lead to undecidable cases for the compiler - i.e. one explicit instance and one through Foo conflicting with each other - , we need some special options to allow the desired behaviour. The rest through is quite straigtforward.
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
class Foo a where
foo :: a -> Int
class Bar a where
bar :: a -> [Int]
instance (Foo a) => Bar a where
bar x = [foo x]
Generally speaking you don't model things with type classes this way[*] - i.e. an instance of a type class should always be some concrete type, though that type itself can be parameteric - e.g. the Show instance for pair has this signature:
instance (Show a, Show b) => Show (a,b) where
Some of the approaches to "Generics" allow you to model a general base case and then have type specific exceptional cases. SYB3 allowed this - perhaps unfortunately SYB3 isn't the common practice Generics library it is Data.Data / Data.Generics which I think is SYB1.
[*] In the wild the story is a little more complicated - as Dario says UndecidableInstances can enable it.

Resources