[Haskell-beginners] Ambiguous type variable

Ovidiu Deac ovidiudeac at gmail.com
Sat Jul 30 22:57:04 CEST 2011


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
<daniel.is.fischer at googlemail.com> wrote:
> 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).



More information about the Beginners mailing list