
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

I can't run your code to be sure, but I think your problem is the ==.
It implies that whatever a is, it has an Eq constraint, but none of
your type signatures imply that. Try this:
case pop EmptyStack) of
(Nothing, EmptyStack) -> blah
otherwise -> do something else or nothing
That way you are using pattern matching instead of equality testing.
On Sat, Jul 30, 2011 at 4:19 PM, Ovidiu Deac
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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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... ) 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

I tried {-# LANGUAGE ExtendedDefaultRules #-} and it didn't work. I
tried to put it both in Stack.hs and in TestStack.hs
Then I tried to be specific about the type in the test.
Both this code:
(pop EmptyStack :: Stack[Char]) ≡ (Nothing, EmptyStack)
and this:
(pop EmptyStack :: Stack[Char]) ≡ (Nothing :: Maybe[Char],
EmptyStack :: Stack[Char])
...give me:
test/TestStack.hs:20:12:
Couldn't match expected type `Stack [Char]'
with actual type `(Maybe a0, Stack a0)'
In the return type of a call of `pop'
In the first argument of `(==)', namely
`(pop EmptyStack :: Stack [Char])'
In the second argument of `it', namely
`((pop EmptyStack :: Stack [Char]) == (Nothing, EmptyStack))'
On Sat, Jul 30, 2011 at 11:37 PM, Daniel Fischer
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... ) 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).

On Saturday 30 July 2011, 22:57:04, Ovidiu Deac wrote:
I tried {-# LANGUAGE ExtendedDefaultRules #-} and it didn't work. I tried to put it both in Stack.hs and in TestStack.hs
Aha. I don't have the impression ExtendedDefaultRules will become a much- used extension.
Then I tried to be specific about the type in the test.
Both this code: (pop EmptyStack :: Stack[Char]) ≡ (Nothing, EmptyStack)
This needs parentheses since the '::' has very low fixity. Without parentheses it's parsed ((pop EmptyStack) :: Stack [Char]) == ... so the type sugnature applies to the result of pop. I wrote ( pop (EmptyStack :: Stack [Char]) == (...,...) ) (extra spaces added to unclutter the outermost parentheses) so that the type signature applies only to EmptyStack. Getting the parentheses for expression type signatures right is notoriously tricky (unless you use parens in every case of the slightest doubt) at first, I should better have given the signature to Nothing, ( pop EmptyStack == (Nothing :: Maybe [Char], EmptyStack) ) that would have been harder to misread.
and this: (pop EmptyStack :: Stack[Char]) ≡ (Nothing :: Maybe[Char], EmptyStack :: Stack[Char])
Note that specifying the type of one subexpression is enough, pop's type then determines the others.

I missed those paranthesis in your initial reply.
Indeed it worked once I put them around EmptyStack :: Stack[Char]
Thanks!
On Sun, Jul 31, 2011 at 12:23 AM, Daniel Fischer
On Saturday 30 July 2011, 22:57:04, Ovidiu Deac wrote:
I tried {-# LANGUAGE ExtendedDefaultRules #-} and it didn't work. I tried to put it both in Stack.hs and in TestStack.hs
Aha. I don't have the impression ExtendedDefaultRules will become a much- used extension.
Then I tried to be specific about the type in the test.
Both this code: (pop EmptyStack :: Stack[Char]) ≡ (Nothing, EmptyStack)
This needs parentheses since the '::' has very low fixity. Without parentheses it's parsed
((pop EmptyStack) :: Stack [Char]) == ...
so the type sugnature applies to the result of pop.
I wrote
( pop (EmptyStack :: Stack [Char]) == (...,...) )
(extra spaces added to unclutter the outermost parentheses) so that the type signature applies only to EmptyStack.
Getting the parentheses for expression type signatures right is notoriously tricky (unless you use parens in every case of the slightest doubt) at first, I should better have given the signature to Nothing,
( pop EmptyStack == (Nothing :: Maybe [Char], EmptyStack) )
that would have been harder to misread.
and this: (pop EmptyStack :: Stack[Char]) ≡ (Nothing :: Maybe[Char], EmptyStack :: Stack[Char])
Note that specifying the type of one subexpression is enough, pop's type then determines the others.
participants (3)
-
Daniel Fischer
-
David McBride
-
Ovidiu Deac