[Haskell-cafe] overloading show function
aditya siram
aditya.siram at gmail.com
Thu Jun 30 00:03:03 CEST 2011
Try enabling OverlappingInstances extension by adding this to the top
of the file:
{-# LANGUAGE OverlappingInstances #-}
-deech
On Wed, Jun 29, 2011 at 4:50 PM, Philipp Schneider
<philipp.schneider5 at gmx.net> wrote:
> Hi cafe,
>
> in my program i use a monad of the following type
>
> newtype M a = M (State -> (a, State))
>
> i use the monad in two different ways. The type variable "a" can be a
> pair as in
>
> interp :: Term -> Environment -> M (Value,Environment)
>
> and it can be just a value as in
>
> type Environment = [(Name, Either Value (M Value))]
>
> now in any case when i print the monad, i just want to print the value
> and never the environment.
>
> More specific i want to use somthing like the following
>
> instance (Show a,Show b) => Show (M (a,b)) where
> show (M f) = let ((v,_), s) = f 0 in
> "Value: " ++ show v ++ " Count: " ++ show s
>
> instance Show a => Show (M a) where
> show (M f) = let (v, s) = f 0 in
> "Value: " ++ show v ++ " Count: " ++ show s
>
> however this gives me the following error message:
>
> Overlapping instances for Show (M (Value, Environment))
> arising from a use of `print'
> Matching instances:
> instance (Show a, Show b) => Show (M (a, b))
> -- Defined at
> /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:78:10-42
> instance Show a => Show (M a)
> -- Defined at
> /home/phil/code/haskell/vorlesung/ue09/ue09-3c3.hs:82:10-29
> In a stmt of an interactive GHCi command: print it
>
> Any ideas how to fix it? Thanks!
> Philipp
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list