Hi,

You might need a class constraint.

instance (Show a) => Show (Stack a) where

This basically lets Haskell know that if your "a" type is Showable then "Stack 
a" is also Showable.

Let me know if this works.

Cheers,

Mark Spezzano


On 31/07/2011, at 6:49 PM, Ovidiu Deac wrote:

> For some reason ghc complains about not being able to call show on an
> Integer (?!?!?)
> 
> Please enlighten me!
> 
> ovidiu
> 
> This is the hspec:
>    it "shows one element"
>        ( show (push 1 EmptyStack) ≡ "Stack(1)")
> 
> ...this is the code:
> 
> data Stack a =
>    EmptyStack |
>    StackEntry a (Stack a)
>    deriving(Eq)
> 
> 
> instance Show (Stack a) where
>    show s =
>        "Stack(" ⊕ (showImpl s) ⊕ ")"
>        where
>            showImpl EmptyStack = ""
>            showImpl (StackEntry x _) = show x
> 
> ...and this is the error:
> 
> src/Stack.hs:12:22:
>    No instance for (Show a)
>      arising from a use of `showImpl'
>    In the first argument of `(++)', namely `(showImpl s)'
>    In the second argument of `(++)', namely `(showImpl s) ++ ")"'
>    In the expression: "Stack(" ++ (showImpl s) ++ ")"
> 
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners


_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to