[Haskell-beginners] Ambiguous type variable

Ovidiu Deac ovidiudeac at gmail.com
Sat Jul 30 22:19:28 CEST 2011


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?

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