
Hi, I just noticed that in ghci: data Test = Test String instance Show Test show $ Test "Hello" Will result in infinite recursion. Is this a known bug? Thanks, titto

On Thursday 08 July 2010 15:20:13, Pasqualino "Titto" Assini wrote:
Hi,
I just noticed that in ghci:
data Test = Test String
instance Show Test
show $ Test "Hello"
Will result in infinite recursion.
Is this a known bug?
It's not a bug. There are default methods in Show for show in terms of showsPrec and for showsPrec in terms of show. You need to define at least one of the two to get a working Show instance, otherwise trying to evaluate (show stuff) will lead to infinite recursion, it's the same with e.g. Eq. Might be a worthwhile feature request to let the compiler emit a warning on every instance declaration where no method is defined.
Thanks,
titto

Thanks for the explanation.
What I meant is not that is a bug that it recurses but rather the fact
that the compiler will accept this incomplete definition without
complaining.
This problem has bitten me twice while trying to use automatic
derivation of a data type in another file.
In my innocence I wrote:
instance Show Test
rather than
deriving instance Show Test
I didn't notice the error as GHC seemed to be happy and then when I
tried to use it: BANG!
Very confusing.
I suppose that Haskell has spoiled me, if it compiles I assume that it
will work :-)
Best,
titto
On 8 July 2010 14:29, Daniel Fischer
On Thursday 08 July 2010 15:20:13, Pasqualino "Titto" Assini wrote:
Hi,
I just noticed that in ghci:
data Test = Test String
instance Show Test
show $ Test "Hello"
Will result in infinite recursion.
Is this a known bug?
It's not a bug.
There are default methods in Show for show in terms of showsPrec and for showsPrec in terms of show. You need to define at least one of the two to get a working Show instance, otherwise trying to evaluate (show stuff) will lead to infinite recursion, it's the same with e.g. Eq.
Might be a worthwhile feature request to let the compiler emit a warning on every instance declaration where no method is defined.
Thanks,
titto
-- Pasqualino "Titto" Assini, Ph.D. http://quicquid.org/

"Pasqualino \"Titto\" Assini"
Thanks for the explanation.
What I meant is not that is a bug that it recurses but rather the fact that the compiler will accept this incomplete definition without complaining.
This problem has bitten me twice while trying to use automatic derivation of a data type in another file.
In my innocence I wrote:
instance Show Test
rather than
deriving instance Show Test
I didn't notice the error as GHC seemed to be happy and then when I tried to use it: BANG!
Very confusing.
I suppose that Haskell has spoiled me, if it compiles I assume that it will work :-)
As I said, there would be no error as all the methods have a definition (whether or not they make sense in this case is a different story); it will still successfully load a file if any methods don't have definitions but will provide a warning in those situations. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Hehe, seems like a -W-mutual-recursive-default-methods option is in order.
On 8 July 2010 15:47, Ivan Lazar Miljenovic
"Pasqualino \"Titto\" Assini"
writes: Thanks for the explanation.
What I meant is not that is a bug that it recurses but rather the fact that the compiler will accept this incomplete definition without complaining.
This problem has bitten me twice while trying to use automatic derivation of a data type in another file.
In my innocence I wrote:
instance Show Test
rather than
deriving instance Show Test
I didn't notice the error as GHC seemed to be happy and then when I tried to use it: BANG!
Very confusing.
I suppose that Haskell has spoiled me, if it compiles I assume that it will work :-)
As I said, there would be no error as all the methods have a definition (whether or not they make sense in this case is a different story); it will still successfully load a file if any methods don't have definitions but will provide a warning in those situations.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Well the problem is that no warnings are generated.
If you have a class with some methods that do not have a default
implementation and you do not provide them when defining your
instance, GHC will at least politely complain.
Ideally, GHC would detect that a Show instance requires one of its two
functions to be declared as they are mutually recursive and complain.
Is that too much to ask?
Maybe it is, and I can see why ghc developers would not bother, but
can we agree that if not a bug, this is at least an inconvenience ?
It took me a while to determine that it was not my own code but rather
the incomplete show instance that was sinking my app :-)
Best,
titto
On 8 July 2010 14:47, Ivan Lazar Miljenovic
"Pasqualino \"Titto\" Assini"
writes: Thanks for the explanation.
What I meant is not that is a bug that it recurses but rather the fact that the compiler will accept this incomplete definition without complaining.
This problem has bitten me twice while trying to use automatic derivation of a data type in another file.
In my innocence I wrote:
instance Show Test
rather than
deriving instance Show Test
I didn't notice the error as GHC seemed to be happy and then when I tried to use it: BANG!
Very confusing.
I suppose that Haskell has spoiled me, if it compiles I assume that it will work :-)
As I said, there would be no error as all the methods have a definition (whether or not they make sense in this case is a different story); it will still successfully load a file if any methods don't have definitions but will provide a warning in those situations.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
-- Pasqualino "Titto" Assini, Ph.D. http://quicquid.org/

"Pasqualino \"Titto\" Assini"
Well the problem is that no warnings are generated.
If you have a class with some methods that do not have a default implementation and you do not provide them when defining your instance, GHC will at least politely complain.
Ideally, GHC would detect that a Show instance requires one of its two functions to be declared as they are mutually recursive and complain.
So you're volunteering to write such functionality? :p -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 8 July 2010 15:11, Ivan Lazar Miljenovic
So you're volunteering to write such functionality? :p
No ! I will patiently wait for the Simons' Dream Team to fix that and in the meantime I will live with the realisation that, having been kicked out of Eden, there is nothing in this world that is absolutely perfect, not even Haskell. Thanks again to everybody for their prompt answers, I had almost forgotten how reactive and comprehensive this mailing list can be :-) titto

On Thursday 08 July 2010 16:11:58, Ivan Lazar Miljenovic wrote:
"Pasqualino \"Titto\" Assini"
writes: Well the problem is that no warnings are generated.
If you have a class with some methods that do not have a default implementation and you do not provide them when defining your instance, GHC will at least politely complain.
Ideally, GHC would detect that a Show instance requires one of its two functions to be declared as they are mutually recursive and complain.
So you're volunteering to write such functionality? :p
Well, I made the suggestion of emitting a warning on instance declarations without method definitions. That would be comparatively easy to implement (even with an additional check to only emit the warning if the class defines any methods) and catch many (if not most) cases. If somebody points me to the relevant modules, I could be persuaded to write it, even.

On Thu, Jul 8, 2010 at 3:45 PM, Daniel Fischer
Well, I made the suggestion of emitting a warning on instance declarations without method definitions. That would be comparatively easy to implement (even with an additional check to only emit the warning if the class defines any methods) and catch many (if not most) cases.
Unfortunately, it would catch some perfectly valid cases, see the list of instances for flat datatypes here: http://hackage.haskell.org/packages/archive/deepseq/1.1.0.0/doc/html/src/Con... This demonstrates that there is at least one (admittedly probably not much more than one) case where a class with methods would have a default implementation that was total and valid in some cases.

On Thursday 08 July 2010 18:24:05, Ben Millwood wrote:
On Thu, Jul 8, 2010 at 3:45 PM, Daniel Fischer
wrote: Well, I made the suggestion of emitting a warning on instance declarations without method definitions. That would be comparatively easy to implement (even with an additional check to only emit the warning if the class defines any methods) and catch many (if not most) cases.
Unfortunately, it would catch some perfectly valid cases, see the list of instances for flat datatypes here:
http://hackage.haskell.org/packages/archive/deepseq/1.1.0.0/doc/html/src /Control-DeepSeq.html
This demonstrates that there is at least one (admittedly probably not much more than one) case where a class with methods would have a default implementation that was total and valid in some cases.
Good point. So one should check for more than one class-method [then defining no methods in the instance declaration is likely to lead to a default-method loop if there are default methods for all, otherwise GHC will warn already]. That can of course still give rise to spurious warnings, but is less likely to.

On Thu, 08 Jul 2010 09:48:34 -0700, Daniel Fischer
On Thursday 08 July 2010 18:24:05, Ben Millwood wrote:
On Thu, Jul 8, 2010 at 3:45 PM, Daniel Fischer
wrote: Well, I made the suggestion of emitting a warning on instance declarations without method definitions. That would be comparatively easy to implement (even with an additional check to only emit the warning if the class defines any methods) and catch many (if not most) cases.
Unfortunately, it would catch some perfectly valid cases, see the list of instances for flat datatypes here:
http://hackage.haskell.org/packages/archive/deepseq/1.1.0.0/doc/html/src /Control-DeepSeq.html
This demonstrates that there is at least one (admittedly probably not much more than one) case where a class with methods would have a default implementation that was total and valid in some cases.
Good point. So one should check for more than one class-method [then defining no methods in the instance declaration is likely to lead to a default-method loop if there are default methods for all, otherwise GHC will warn already]. That can of course still give rise to spurious warnings, but is less likely to.
I would think that only mutually recursive default methods would require respecification and that there could be any number of default methods that were reasonable as is. Since it's probably quite difficult for the Haskell compiler to analytically detect non-terminating v.s. terminating mutual recursion it may be useful to define an explicit comment flag for this case. For example: class Show a where shows = showsPrec 5 showsPrec _ = shows {-# REDEFINE_ONE: shows showsPrec #-} This would fairly simply allow a warning to be generated for an instance which did not redefine one of the identified methods; it would capture that requirement in the same place the recursive definition was defined, it would avoid false warnings, and it would be backward compatible (and it might be Haddock-able as well). -- -KQ

"Kevin Quick"
I would think that only mutually recursive default methods would require respecification and that there could be any number of default methods that were reasonable as is. Since it's probably quite difficult for the Haskell compiler to analytically detect non-terminating v.s. terminating mutual recursion it may be useful to define an explicit comment flag for this case.
For example:
class Show a where shows = showsPrec 5 showsPrec _ = shows {-# REDEFINE_ONE: shows showsPrec #-}
This would fairly simply allow a warning to be generated for an instance which did not redefine one of the identified methods; it would capture that requirement in the same place the recursive definition was defined, it would avoid false warnings, and it would be backward compatible (and it might be Haddock-able as well).
This should be generalised IMO, since there might be cases where you have to redefine either (foo && bar) || baz; of course, that makes the syntax specification, etc. of the pragma more difficult... -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Fri, 09 Jul 2010 16:26:13 -0700, Ivan Lazar Miljenovic
"Kevin Quick"
writes: I would think that only mutually recursive default methods would require respecification and that there could be any number of default methods that were reasonable as is. Since it's probably quite difficult for the Haskell compiler to analytically detect non-terminating v.s. terminating mutual recursion it may be useful to define an explicit comment flag for this case.
For example:
class Show a where shows = showsPrec 5 showsPrec _ = shows {-# REDEFINE_ONE: shows showsPrec #-}
This would fairly simply allow a warning to be generated for an instance which did not redefine one of the identified methods; it would capture that requirement in the same place the recursive definition was defined, it would avoid false warnings, and it would be backward compatible (and it might be Haddock-able as well).
This should be generalised IMO, since there might be cases where you have to redefine either (foo && bar) || baz; of course, that makes the syntax specification, etc. of the pragma more difficult...
I'm having trouble envisioning a restriction case such as you describe. Can you provide an example? The comment can't dictate that the resulting redefined method isn't still mutually recursive, but the warning for the lack of any override should provide enough of a trigger for the developer to read the docs/code and write an appropriate method. If foo, bar, and baz are all interrelated it seems to me that an appropriate override of any of them could provide the necessary exit from recursion. That's probably an interesting assertion that one of the category theorists around here could prove or disprove. ;-) -- -KQ

On Fri, Jul 9, 2010 at 8:46 PM, Kevin Quick
On Fri, 09 Jul 2010 16:26:13 -0700, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
"Kevin Quick"
writes: I would think that only mutually recursive default methods would
require respecification and that there could be any number of default methods that were reasonable as is. Since it's probably quite difficult for the Haskell compiler to analytically detect non-terminating v.s. terminating mutual recursion it may be useful to define an explicit comment flag for this case.
For example:
class Show a where shows = showsPrec 5 showsPrec _ = shows {-# REDEFINE_ONE: shows showsPrec #-}
This would fairly simply allow a warning to be generated for an instance which did not redefine one of the identified methods; it would capture that requirement in the same place the recursive definition was defined, it would avoid false warnings, and it would be backward compatible (and it might be Haddock-able as well).
This should be generalised IMO, since there might be cases where you have to redefine either (foo && bar) || baz; of course, that makes the syntax specification, etc. of the pragma more difficult...
I'm having trouble envisioning a restriction case such as you describe. Can you provide an example?
Examples: class Bifunctor f where bimap :: (a -> b) -> (c -> d) -> f a c -> f b d first :: (a -> b) -> f a c -> f b c second :: (a -> b) -> f c a -> f c b first f = bimap f id second = bimap id bimap f g = second g . first f {-# MUTUAL = first second | bimap #-} The existing definition of Arrow is somewhat unsatisfying because its product bifunctor definition (given by first, second and (***)) is asymmetric. They choose to require you to define first, but could very well use the same trick. (I am not advocating changing the well documented historical definition of Arrow, just providing another example in the same vein.) class Category a => Arrow a where arr :: (b -> c) -> a b c first :: a b c -> a (b,d) (c,d) second :: a b c -> a (d,b) (d,c) (***) :: a b c -> a b' c' -> a (b,b') (c,c') (&&&) :: a b c -> a b c' -> a b (c,c') first = (*** id) second = (id ***) f *** g = first f >>> second g f &&& g = arr (\b -> (b,b)) >>> f *** g {-# MUTUAL first second | (***) #-} An example that almost works would be Monad/Comonad where you can define in terms of return/fmap/join or return/bind. However, the definition of fmap is in another class, but if it wasn't: class Comonad w where liftW :: (a -> b) -> w a -> w b extract :: w a -> a extend :: (w a -> b) -> w a -> w b duplicate :: w a -> w (w a) extend = fmap f . duplicate duplicate = extend id {-# MUTUAL liftW duplicate | extend #-}
The comment can't dictate that the resulting redefined method isn't still mutually recursive, but the warning for the lack of any override should provide enough of a trigger for the developer to read the docs/code and write an appropriate method. If foo, bar, and baz are all interrelated it seems to me that an appropriate override of any of them could provide the necessary exit from recursion.
It turns out to be fairly tricky to pull off the definition in such a way that you can define any one combinator in turn of the others in a big long cycle. Foldable does this for instance in such a way that foldMap and foldr are defined cyclically. That's probably an interesting assertion that one of the category theorists
around here could prove or disprove. ;-)
I hope the above demonstrate that there are at least some fairly reasonable (and, given your request, appropriately category theoretic!) examples where one would want the ability to specify that there is more than one member of a minimal mutual definition. =) -Edward Kmett

On Fri, 09 Jul 2010 18:57:34 -0700, Edward Kmett
I hope the above demonstrate that there are at least some fairly reasonable (and, given your request, appropriately category theoretic!) examples where one would want the ability to specify that there is more than one member of a minimal mutual definition. =)
It does, thanks! (And thanks as well to Alexander for the description of proofs). This confirms Ivan's proposal a more general form allowing grouping (&) and exclusion (|) would be needed. The question now is: is that enough and is this a useful approach to the problem that should be moved forward as a more formal suggestion? -- -KQ

On Jul 9, 2010, at 5:46 PM, Kevin Quick wrote:
That's probably an interesting assertion that one of the category theorists around here could prove or disprove. ;-)
It's not too hard. I don't like thinking about it in terms of category theory, though. It's easier to think about it in terms of universal quantification. The assertion is equivalent to the claim that (forall x, forall y, P x y) iff (forall y, forall x, P x y), though you have to do quite a bit of packing and unpacking to get there. Another way to see it is in terms of recursion on initial algebras. Given an initial algebra A, and an initial algebra B, we'll say that A -> B represents the construction of attaching a copy of B to every element of A. We can assume that A and B are disjoint, because we can find a normal form A' -> B' for which A' and B' are disjoint, and such that A -> B is isomorphic to A' -> B'. (To see that, assume that some subalgebra C is contained in both A and B. Attaching a copy of B to every element of A means attaching a copy of C to each element, and also B \ C. But A already contains C. So A -> B is isomorphic to A -
B \ C). Note that since we can assume A and B are disjoint, we can also assume A and B are NOT mutually recursive. We can always find a way to break that mutual recursion up.
I'm not sure how to prove that A -> B and B -> A, as I defined them, are isomorphic. But they are. I guess we can re-interpret A and B as meet semi-lattices, and A -> B and B -> A as their products.

Hi titto, You should try to give a complete list of steps which can be run to reproduce your problem. This also includes ghci --version output and maybe some info about the OS you're working on. So how you you load the code into ghci? Using ghci File.hs or :l ? In any case you want to declare the show method: -- yes, I know I should just use 'deriving (Show)' because most -- developers expect Read Show instances to work the common way -- which means they serialize and unserialize data types in a reliable -- way ... instance Show Test where show (Test s) = "my show implementation of Test: Test " ++ s Marc Weber

"Pasqualino \"Titto\" Assini"
Hi,
I just noticed that in ghci:
data Test = Test String
instance Show Test
show $ Test "Hello"
Well, for starters you specify such a thing in ghci, so presumably you loaded a file with these definitions.
Will result in infinite recursion.
Is this a known bug?
Not a bug. Let us consider the definition of the Show class: class Show a where showsPrec :: Int -> a -> ShowS showsPrec _ x s = show x ++ s -- | A specialised variant of 'showsPrec', using precedence context -- zero, and returning an ordinary 'String'. show :: a -> String show x = shows x "" showList :: [a] -> ShowS showList ls s = showList__ shows ls s Note that showsPrec and show are by default mutually recursive, and that all the class methods have a default definition. Thus, just saying "instance Show Test" like you have above is valid, but not very helpful. This is why the documentation for the Show class specifies that the minimal complete definition is either showsPrec or show: defining at least one of these will cut out of the infinite recursion loop. Of course, a better question is: why are you writing your own instance for Show? Unless your data type is complex, you should just have "deriving (Show)" (as well as classes such as Eq, Ord and Read) attached to your datatype definition. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
participants (9)
-
Alexander Solla
-
Ben Millwood
-
Christopher Done
-
Daniel Fischer
-
Edward Kmett
-
Ivan Lazar Miljenovic
-
Kevin Quick
-
Marc Weber
-
Pasqualino "Titto" Assini