How do I resolve this compile error: Ambiguous type variable `a1' in the constraint - haskell

One could think of this case as follows:
The application dynamically loads a module, or there is a list of functions from which the user chooses, etc. We have a mechanism for determining whether a certain type will successfully work with a function in that module. So now we want to call into that function. We need to force it to make the call. The function could take a concrete type, or a polymorphic one and it's the case below with just a type class constraint that I'm running into problems with it.
The following code results in the errors below. I think it could be resolved by specifying concrete types but I do not want to do that. The code is intended to work with any type that is an instance of the class. Specifying a concrete type defeats the purpose.
This is simulating one part of a program that does not know about the other and does not know the types of what it's dealing with. I have a separate mechanism that allows me to be sure that the types do match up properly, that the value sent in really is an instance of the type class. That's why in this case, I don't mind using unsafeCoerce. But basically I need a way to tell the compiler that I really do know it's ok and do it anyway even though it doesn't know enough to type check.
{-# LANGUAGE ExistentialQuantification, RankNTypes, TypeSynonymInstances #-}
module Main where
import Unsafe.Coerce
main = do
--doTest1 $ Hider "blue"
doTest2 $ Hider "blue"
doTest1 :: Hider -> IO ()
doTest1 hh#(Hider h) =
test $ unsafeCoerce h
doTest2 :: Hider -> IO ()
doTest2 hh#(Hider h) =
test2 hh
test :: HasString a => a -> IO ()
test x = print $ toString x
test2 :: Hider -> IO ()
test2 (Hider x) = print $ toString (unsafeCoerce x)
data Hider = forall a. Hider a
class HasString a where
toString :: a -> String
instance HasString String where
toString = id
Running doTest1
[1 of 1] Compiling Main ( Test.hs, Test.o )
Test.hs:12:3:
Ambiguous type variable `a1' in the constraint:
(HasString a1) arising from a use of `test'
Probable fix: add a type signature that fixes these type variable(s)
In the expression: test
In the expression: test $ unsafeCoerce h
In an equation for `doTest1':
doTest1 hh#(Hider h) = test $ unsafeCoerce h
Running doTest2
[1 of 1] Compiling Main ( Test.hs, Test.o )
Test.hs:12:3:
Ambiguous type variable `a1' in the constraint:
(HasString a1) arising from a use of `test'
Probable fix: add a type signature that fixes these type variable(s)
In the expression: test
In the expression: test $ unsafeCoerce h
In an equation for `doTest1':
doTest1 hh#(Hider h) = test $ unsafeCoerce h

I think it could be resolved by specifying concrete types but I do not want to do that.
There's no way around it though with unsafeCoerce. In this particular case, the compiler can't infer the type of unsafeCoerce, because test is still to polymorphic. Even though there is just one instance of HasString, the type system won't use that fact to infer the type.
I don't have enough information about your particular application of this pattern, but I'm relatively sure that you need to rethink the way you use the type system in your program. But if you really want to do this, you might want to look into Data.Typeable instead of unsafeCoerce.

Modify your data type slightly:
data Hider = forall a. HasString a => Hider a
Make it an instance of the type class in the obvious way:
instance HasString Hider where
toString (Hider x) = toString x
Then this should work, without use of unsafeCoerce:
doTest3 :: Hider -> IO ()
doTest3 hh = print $ toString hh
This does mean that you can no longer place a value into a Hider if it doesn't implement HasString, but that's probably a good thing.
There's probably a name for this pattern, but I can't think what it is off the top of my head.

Related

Why such different behaviour with `Ambiguous type..` error (in ghci)?

This example works with ghci, load this file:
import Safe
t1 = tailMay []
and put in ghci:
> print t1
Nothing
But if we add analogous definition to previous file, it doesn't work:
import Safe
t1 = tailMay []
t2 = print $ tailMay []
with such error:
* Ambiguous type variable `a0' arising from a use of `print'
prevents the constraint `(Show a0)' from being solved.
Probable fix: use a type annotation to specify what `a0' should be.
These potential instances exist:
instance Show Ordering -- Defined in `GHC.Show'
instance Show Integer -- Defined in `GHC.Show'
instance Show a => Show (Maybe a) -- Defined in `GHC.Show'
...plus 22 others
That is 3rd sample for ghc with the same error:
import Safe
t1 = tailMay
main = do
print $ t1 []
print $ t1 [1,2,3]
Why? And how to fix the second sample without explicit type annotation?
The issue here is that tailMay [] can generate an output of type Maybe [a] for any a, while print can take an input of type Maybe [a] for any a (in class Show).
When you compose a "universal producer" and a "universal consumer", the compiler has no idea about which type a to pick -- that could be any type in class Show. The choice of a could matter since, in principle, print (Nothing :: Maybe [Int]) could print something different from print (Nothing :: Maybe [Bool]). In this case, the printed output would be the same, but only because we are lucky.
For instance print ([] :: [Int]) and print ([] :: [Char]) will print different messages, so print [] is ambiguous. Hence, GHC reject it, and requires an explicit type annotation (or a type application # type, using an extension).
Why, then, such ambiguity is accepted in GHCi? Well, GHCi is meant to be used for quick experiments, and as such, as a convenience feature, it will try hard to default these ambiguous a. This is done using the extended defaulting rules, which could (I guess) in principle be turned on in GHC as well by turning on that extension.
This is, however, not recommended since sometimes the defaulting rule can choose some unintended type, making the code compile but with an unwanted runtime behavior.
The common solution to this issue is using an annotation (or # type), because it provides more control to the programmer, makes the code easier to read, and avoids surprises.

Explicit type conversion?

This is an example function:
import qualified Data.ByteString.Lazy as LAZ
import qualified Data.ByteString.Lazy.Char8 as CHA
import Network.Wreq
makeRequest :: IO (Network.Wreq.Response LAZ.ByteString)
makeRequest = do
res <- get "http://www.example.com"
let resBody = res ^. responseBody :: CHA.ByteString
--Do stuff....
return (res)
I'm struggling to understand the exact purpose of CHA.ByteString in this line:
let resBody = res ^. responseBody :: CHA.ByteString
Is this explicitly stating the type must be CHA.ByteString? Or does it serve another role?
Yes, this is just explicitly stating that the type must be CHA.ByteString. This does (by itself) not incur any sort of conversion, it's just a hint for the compiler (and/or the reader) that res must have this type.
These kinds of local annotations are needed when a value is both produced from a function with polymorphic result, and only consumed by functions with polymorphic argument. A simple example:
f :: Int -> Int
f = fromEnum . toEnum
Here, toEnum converts an integer to a arbitrary enumerable type – could for instance be Char. Whatever type you'd choose, fromEnum would be able to convert it back... trouble is, there is no way to decide which type should be used for the intermediate result!
No instance for (Enum a0) arising from a use of ‘fromEnum’
The type variable ‘a0’ is ambiguous
Note: there are several potential instances:
instance Integral a => Enum (GHC.Real.Ratio a)
-- Defined in ‘GHC.Real’
instance Enum Ordering -- Defined in ‘GHC.Enum’
instance Enum Integer -- Defined in ‘GHC.Enum’
...plus 7 others
In the first argument of ‘(.)’, namely ‘fromEnum’
In the expression: fromEnum . toEnum
In an equation for ‘f’: f = fromEnum . toEnum
For some simple number classes, Haskell has defaults, so e.g. fromIntegral . round will automatically use Integer. But there are no defaults for types like ByteString, so with a polymorphic-result function like responseBody, you either need to pass the result to a monomorphic function that can only accept CHA.ByteString, or you need to add an explicit annotation that this should be the type.
The notation x :: T reads expression x has type T
This may be necessary in the presence of type classes and higher ranked types to enable the compiler to type check the program. For example:
main = print . show . read $ "1234"
is ambiguous, since the compiler cannot know which of the overloaded read functions to use.
In addition, it is possible to narrow the type the compiler would infer. Example:
1 :: Int
Finally, a type signature like this is often used to make the program more readable.

Incomplete implicit type inference in Haskell

Let's consider the following example:
data A = A{x::Int} deriving(Show)
instance Func_f (A -> String) where
f _ = "ala"
class Func_f a where
f :: a
main :: IO ()
main = do
let
a = A 5
x = f a
print 5
compiled with ghc -XFlexibleInstances main.hs
(I've tried -XExtendedDefaultRules, but without any progress)
Why while compiling we get an error?:
main.hs:25:21:
No instance for (Func_f (A -> t0)) arising from a use of `f'
The type variable `t0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there is a potential instance available:
instance Func_f (A -> String) -- Defined at main.hs:7:10
Possible fix: add an instance declaration for (Func_f (A -> t0))
In the expression: f a
In an equation for `x': x = f a
In the expression:
do { let a = A 5
x = f a;
print 5 }
There is only one instance for Func_f, so Haskell should be able to know the result of x = f a. You can fix the error by providing the type manually, like this: x = f a :: String, but this is not suitable for my case, because I'm generating Haskell code and I would love the Haskell's type inferencer to do this job for me.
You're running into the open world assumption. The basic idea is that GHC always assumes that you could add more class instances to your code. Moreover, you cannot control how instances get exported and imported between modules. So relying on only having one instance of a particular class is not going to work and would lead to weird bugs.
Essentially, nothing stops you--or anybody else, for that matter--from writing another instance like:
instance Func_f (A -> Int) where
f _ = 10
and it would then be impossible to figure out which one you wanted in your code. This could cause your code to break just from linking against another module!
However, if you actually used the value, chances are it would get its type constrained by some other parameter and the ambiguity would go away. For example, the following works:
main :: IO ()
main = do
let a = A 5
x = f a
putStr x
Basically, this is one of those cases (similar to read . show) where a type signature is simply unavoidable because of how GHC treats typeclass instances.
There is only one instance for Func_f, so Haskell should be able to know the result of x = f a
This violates the open world assumption.

Haskell - Ambiguous type variable

I am having trouble with ambiguous types in Haskell. I started out with the following:
module GameState
( GameState(..)
, GameStateMonad
, module Control.Monad.Trans
, module Control.Monad.Trans.State.Lazy
, Blank(..)
) where
import Control.Monad.Trans
import Control.Monad.Trans.State.Lazy
type GameStateMonad a b = StateT a IO b
class GameState a where
update :: Double -> GameStateMonad a ()
update deltaTime = return ()
draw :: GameStateMonad a ()
draw = return ()
getNextState :: GameState b => GameStateMonad a (Maybe b)
getNextState = return Nothing
isStateFinished :: GameStateMonad a Bool
isStateFinished = return True
-- This is just a dummy data and instance declaration to demonstrate the error
data Blank = Blank
instance GameState Blank
Then when I try to run the following in ghci:
runStateT getNextState Blank
I get:
Ambiguous type variable `b0' in the constraint:
(GameState b0) arising from a use of `getNextState'
Probable fix: add a type signature that fixes these type variable(s)
...
I thought it was complaining that my default implementation of the getNextState function didn't specify a concrete type, so I tried the following:
getNextState :: GameState b => GameStateMonad a (Maybe b)
getNextState = return (Nothing :: Maybe Blank)
Unfortunately I got this error while compiling:
Could not deduce (b ~ Blank)
from the context (GameState a)
bound by the class declaration for `GameState'
at GameState.hs:(14,1)-(25,33)
or from (GameState b)
bound by the type signature for
getNextState :: GameState b => GameStateMonad a (Maybe b)
at GameState.hs:22:5-50
`b' is a rigid type variable bound by
the type signature for
getNextState :: GameState b => GameStateMonad a (Maybe b)
at GameState.hs:22:5
...
But I found that adding a type signature when I call getNext state allows the code to run:
runStateT (getNextState :: GameStateMonad Blank (Maybe Blank)) Blank
Unfortunately this stops me from making generic code to handle game states. It also makes little sense to me. What's the point in returning a polymorphic type if you have to give it an explicit type after it's returned? The original issue is also really confusing to me because I can make a function as follows:
test :: Num a => Maybe a
test = Nothing
And have no problems running it. Shouldn't this complain about ambiguous types like my original code? Also when giving the return value an explicit type I cannot compile it, like before:
test :: Num a => Maybe a
test = Nothing :: Maybe Int
I don't see why this is a problem. Int is an instance of type Num so the type of the function is correct.
I have four questions:
Why does giving an explicit type when returning an element of a typeclass cause a compile error?
Why does returning an ambiguous Maybe value inside of getNextState cause an error but inside test it does not?
Why does this error occur without me calling a function on the returned polymorphic data, as explained here?
In the link above, the answer mentions that "[you get this error] because you have something that produces a polymorphic result, then apply a function that takes a polymorphic argument to that result, such that the intermediate value's type is unknown". Doesn't this mean that functions that return a polymorphic result are essentially useless?
Thanks.
Cat Plus Plus has already explained why
getNextState :: GameState b => GameStateMonad a (Maybe b)
getNextState = return (Nothing :: Maybe Blank)
doesn't work, so I can be short on that. The type signature promises that getNextState can deliver a value of type Maybe b for whatever type b the caller demands. It's the caller of the function who decides what type it shall return if a function has polymorphic return type. So the signature promises "whatever you want, as long as it's a GameState instance", but the implementation says "No, I don't care what you ordered, I return a Blank".
Ambiguous type variable `b0' in the constraint:
(GameState b0) arising from a use of `getNextState'
Probable fix: add a type signature that fixes these type variable(s)
from typing
runStateT getNextState Blank
at the ghci prompt. If you ask ghci for the type of that, it will tell you
runStateT getNextState Blank :: GameState b => IO (Maybe b)
(no guarantees about the choice of type variable). But there is no context, so ghci doesn't know which type to instantiate b with. And so it doesn't know which implementation of getNextState it should call [or, which dictionary it should pass, if we look at GHC's implementation of type classes]. It has no way of resolving that ambiguity, so it tells you about it and suggests how you could resolve it.
test :: Num a => Maybe a
test = Nothing
Yes, that's in principle the same problem, when you type test at the ghci prompt. But there are special rules for resolving ambiguous type variables when there is one numeric class involved (where ambiguities are most frequent, literals are already ambiguous), and all involved constraints are simple and concern classes of the Prelude or the standard libraries. In that case, ambiguous type variables are instantiated by defaulting, so ghci would choose to instantiate a with Integer and print the Nothing of the type Maybe Integer.
Your GameState class is not defaultable, that's the difference between these examples.
Why does this error occur without me calling a function on the returned polymorphic data, as explained here?
Because you're not calling any function that would determine the type. If you had a function of type
foo :: Blank -> Int
and typed
runStateT getNextState Blank >>= print . maybe 0 foo
the use of foo would determine b and all would be swell.
The problem would however not be solved but exacerbated, if you called a polymorphic function (whose argument type cannot be inferred from its result type), as in the linked example. Then the ambiguous type is no longer reachable from the outside, and it can never be resolved. Then the only way is to provide a type signature that resolves the ambiguity.
Doesn't this mean that functions that return a polymorphic result are essentially useless?
Oh no, they are immensely useful. Look at read, or fromInteger, realToFrac, ...
The point is, that the type at which they shall be used must somehow be determined where they are used. Most of the time that is done by the calling context, but sometimes an explicit type signature is necessary.
I'm not sure what you're trying to achieve by making GameState a typeclass. You might be too much in OOP mindset here — typeclasses are not OOP classes. A set of game states will probably be closed, so it might make more sense to just make it a single ADT.
Why does giving an explicit type when returning an element of a typeclass cause a compile error?
Look at your function's signature: GameState b => GameStateMonad a (Maybe b). Now remember that this implies forall b. GameState b => GameStateMonad a (Maybe b).
Implementation of the function cannot decide what b is — it must work for all of them (as long as they fit in constraints), because it's up for the caller to decide.
That's why return (Nothing :: Maybe Blank) is an error — it doesn't work for all types b — it only works for Blank. "Could not deduce (b ~ Blank)" means GHC can't prove type equality here. Same thing goes for Nothing :: Maybe Int. And that's also why adding type signature in the call site works.
I'll write something on ambiguities later maybe. I'm still pretty sure you're overengineering this code anyway, so the solution is to not do that.

Ambiguous Types, and Defaults for Overloaded Numeric Operations

import Data.Dynamic
default(Integer,Double)
a :: Num a => a
a = 5
-- show :: Show a => a -> String
-- toDyn :: Typeable a => a -> Dynamic
main :: IO ()
-- main = print $ show a -- *** THIS LINE WORKS WELL
main = print $ toDyn a -- *** THIS LINE LEADS TO AN AMBIGUOUS TYPE ERROR
I don't understand why the first "main" version works, and not the second.
Is there someone who can help me ?
Thanks in advance for your reply.
From the Haskell report:
In situations where an ambiguous type is discovered, an ambiguous type variable, v, is defaultable if:
v appears only in constraints of the form C v, where C is a class, and
at least one of these classes is a numeric class, (that is, Num or a subclass of Num), and
all of these classes are defined in the Prelude or a standard library
Your example fails because unlike Show, Typeable is not one of the classes specified in the third point, so no defaulting is performed.

Resources