[Haskell-beginners] Ambiguous type variable

Daniel Fischer daniel.is.fischer at googlemail.com
Sat Jul 30 22:37:39 CEST 2011


On Saturday 30 July 2011, 22:19:28, Ovidiu Deac wrote:
> I'm playing with Haskell so I wrote a stack module (see the code
> below). I have a problem with the pop function which returns a tuple
> (Nothing, EmptyStack) if called with an EmptyStack.
> 
> I kind of understand that the compiler cannot cannot figure out what
> type to use for a. But how could I tell the compiler that if the list
> is empty I don't care about that type?

You can't really, the compiler needs a specific type to know which Eq 
instance to use.

If you had a Num constraint, the defaulting rules (language report,
http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-790004.3.4
) would let the compiler pick a type (normally Integer, unless you have a 
default declaration that says otherwise).
I'm not sure what GHC's ExtendedDefaultRules extension does, but there's a 
good chance that a

{-# LANGUAGE ExtendedDefaultRules #-}

pragma at the top will make it compile (and let GHC pick () for the type).

Another option is that you choose a type and write your condition

   (pop (EmptyStack :: Stack [Char]) == (Nothing, EmptyStack))

(which is portable, hence preferable).

> 
> Thanks,
> Ovidiu
> 
> /////////////////
> This is the hspec
> ...
>     it "pop empty stack gives Nothing"
>         ( (pop EmptyStack) ≡ (Nothing, EmptyStack))
> ...
> 
> This is the code:
> module Stack where
> import Prelude
> 
> data Stack a =
>     EmptyStack |
>     StackEntry a (Stack a)
>     deriving(Show, Eq)
> ...
> pop :: Stack a →  (Maybe a, Stack a)
> pop EmptyStack = (Nothing, EmptyStack)
> pop (StackEntry a s) = ((Just a), s)
> 
> ...and this is the error I get:
> test/TestStack.hs:20:28:
>     Ambiguous type variable `a0' in the constraint:
>       (Eq a0) arising from a use of `=='
>     Probable fix: add a type signature that fixes these type variable(s)
>     In the second argument of `it', namely
>       `((pop EmptyStack) == (Nothing, EmptyStack))'
>     In the expression:
>       it
>         "pop empty stack gives Nothing"
>         ((pop EmptyStack) == (Nothing, EmptyStack))
>     In the second argument of `describe', namely
>       `[it "empty stack is empty" (isEmpty EmptyStack),
>         it
>           "non-empty stack is not empty"
>           (not (isEmpty (push 10 EmptyStack))),
>         it
>           "push then pop retrieves the same value"
>           ((pop $ push 10 EmptyStack) == (Just 10, EmptyStack)),
>         it
>           "push push then pop retrieves the last value"
>           ((pop $ push 2 (push 1 EmptyStack))
>          ==
>            (Just 2, (push 1 EmptyStack))),
>         ....]'
> make: *** [test] Error 1
> 




More information about the Beginners mailing list