overloading show function

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

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thank you very much, this worked. On 06/30/2011 12:03 AM, aditya siram wrote:
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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Philipp, On 06/29/2011 11:50 PM, Philipp Schneider wrote:
Hi cafe,
in my program i use a monad of the following type
newtype M a = M (State -> (a, State))
btw., it looks like you just rebuilt the State monad.
...
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
This is a well-known issue. The problem is as follows: Your second instance declares an instance Show (M a) for any type a. If a is of the Form (b, c), we can derive a tuple instance from that. This however conflicts with the tuple instance declared above. If you want GHC to choose the most specific instance (which would be your first one for tuples), use the {-# LANGUAGE OverlappingInstances #-} pragma. Be careful with this however, as it might lead to unexpected results. For a similar problem, you may want to consult the haskell wiki[1]. -- Steffen [1] http://haskell.org/haskellwiki/GHC/AdvancedOverlap

Am 29.06.2011 um 23:50 schrieb Philipp Schneider:
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))]
Simple rule: Never return an environment! An environment contains local variable bindings, so no subcomputation will ever need to return its environment. I don't know anything about the language your program interprets, but I'm sure that you can rewrite function interp as interp :: Term -> Environment -> M Value The structure of the interpreter will become clearer and your problem will vanish.
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"An environment contains local variable bindings, so no subcomputation will ever need to return its environment. " - That is not true. A subcomputation can possible modify an environment except the language forbids such a case. On 06/30/2011 02:36 PM, Holger Siegel wrote:
Am 29.06.2011 um 23:50 schrieb Philipp Schneider:
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))] Simple rule: Never return an environment!
An environment contains local variable bindings, so no subcomputation will ever need to return its environment. I don't know anything about the language your program interprets, but I'm sure that you can rewrite function interp as
interp :: Term -> Environment -> M Value
The structure of the interpreter will become clearer and your problem will vanish.
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 06/30/2011 02:36 PM, Holger Siegel wrote:
Am 29.06.2011 um 23:50 schrieb Philipp Schneider:
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))] Simple rule: Never return an environment!
An environment contains local variable bindings, so no subcomputation will ever need to return its environment. I don't know anything about the language your program interprets, but I'm sure that you can rewrite function interp as
interp :: Term -> Environment -> M Value
The structure of the interpreter will become clearer and your problem will vanish.
Hello Holger, I'm giving two lambda interpreters. The first one is a call by value interpreter, the second one a call by name interpreter which are described in Philip Wadler's paper "The essence of functional programming" page 4 and 12. Now my task is to write a lazy lambda interpreter. The exercise is more playful than serious since Wadler's call by value interpreter is, since written in lazy Haskell, already a lazy lambda interpreter. (To get true call by value one would need to force evaluations of the arguments with the seq function.) For both of Wadler's interpreters the type of the interpertation function is: interp :: Term -> Environment -> M Value Now to simulate lazy interpretation i need to do the following: Decide is the value I need already evaluated or is it still a computation. In the later case I need to evaluate it and save its value in the environment. This is the reason I changed the type of the interpretation function to: interp :: Term -> Environment -> M (Value,Environment) I appened my full interpreter. If you can find a more elegant way to save the newly interpreted values, you are more than welcome to show my how to do it. Cheers, Philipp

On 06/30/2011 08:25 PM, Philipp Schneider wrote:
On 06/30/2011 02:36 PM, Holger Siegel wrote:
Am 29.06.2011 um 23:50 schrieb Philipp Schneider:
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))] Simple rule: Never return an environment!
An environment contains local variable bindings, so no subcomputation will ever need to return its environment. I don't know anything about the language your program interprets, but I'm sure that you can rewrite function interp as
interp :: Term -> Environment -> M Value
The structure of the interpreter will become clearer and your problem will vanish.
Hello Holger,
I'm giving two lambda interpreters. The first one is a call by value interpreter, the second one a call by name interpreter which are described in Philip Wadler's paper "The essence of functional programming" page 4 and 12. Now my task is to write a lazy lambda interpreter. The exercise is more playful than serious since Wadler's call by value interpreter is, since written in lazy Haskell, already a lazy lambda interpreter. (To get true call by value one would need to force evaluations of the arguments with the seq function.) For both of Wadler's interpreters the type of the interpertation function is: interp :: Term -> Environment -> M Value
Now to simulate lazy interpretation i need to do the following: Decide is the value I need already evaluated or is it still a computation. In the later case I need to evaluate it and save its value in the environment. This is the reason I changed the type of the interpretation function to: interp :: Term -> Environment -> M (Value,Environment)
I appened my full interpreter. If you can find a more elegant way to save the newly interpreted values, you are more than welcome to show my how to do it.
Cheers, Philipp I forgot to add the interpreter.
participants (5)
-
aditya siram
-
Holger Siegel
-
Philipp Schneider
-
Steffen Schuldenzucker
-
Wolfgang Braun