suggestion: use lazy pattern matching for Monoid instances of tuples

Dear haskellers, currently the instances are defined as |instance (Monoid a,Monoid b) =>Monoid (a,b)where mempty = (mempty, mempty) (a1,b1) `mappend` (a2,b2) = (a1 `mappend` a2, b1 `mappend` b2)| However for some applications this isn't lazy enough, for example |-- | Build two lists by folding on a pair of `Endo` monoids. test = head $ appEndo (fst $ foldMap (f &&& f) [1..]) [] where f =Endo . (:)| never terminates because of the unnecessary pattern matching on the constructor |(,)| forces evaluation of the whole infinite list. I suggest to change all Monoid instances for tuples to be like | instance (Monoid a,Monoid b) =>Monoid (a,b)where mempty = (mempty, mempty) ~(a1,b1) `mappend` ~(a2,b2) = (a1 `mappend` a2, b1 `mappend` b2) -- ^^^ ^^^| which fixes the problem. Best regards, Petr

Am 17.08.2013 22:31, schrieb Petr Pudlák:
Dear haskellers,
currently the instances are defined as
|instance (Monoid a,Monoid b) =>Monoid (a,b)where mempty = (mempty, mempty) (a1,b1) `mappend` (a2,b2) = (a1 `mappend` a2, b1 `mappend` b2)|
I think that this instance is correct, since it must hold forall x. mappend mempty x = x With your instance you get for x=undefined: mappend mempty undefined = (undefined, undefined) However, the "instance Monoid ()" is too lazy, such that it does not satisfy the identity law.

Sat 17 Aug 2013 10:40:50 PM CEST, Henning Thielemann napsal:
Am 17.08.2013 22:31, schrieb Petr Pudlák:
Dear haskellers,
currently the instances are defined as
|instance (Monoid a,Monoid b) =>Monoid (a,b)where mempty = (mempty, mempty) (a1,b1) `mappend` (a2,b2) = (a1 `mappend` a2, b1 `mappend` b2)|
I think that this instance is correct, since it must hold
forall x. mappend mempty x = x
With your instance you get for x=undefined:
mappend mempty undefined = (undefined, undefined)
However, the "instance Monoid ()" is too lazy, such that it does not satisfy the identity law.
I have some doubts in this reasoning. Here `undefined` isn't a value we can compare, it represents a non-terminating program. How can we compare two non-terminating programs for equality? I'd say we can only say that two non-terminating programs are unequal, if they produce a partial results that are different. For example, `(undefined, 1)` is unequal `(undefined, 2)`. But how can we observe that `undefined` is distinct from `(undefined, undefined)`? We can't write a correctly terminating program that would observe this inequality (of course, unless we use IO and exception catching). The only thing this additional laziness can change is to make some non-terminating programs terminating. This is very different than from having an instance that fails an equality law with defined values, in such a case we'd be able to observe some programs behave incorrectly. I'd say that with `undefined` we can fail other equality laws. For example: For `MonadPlus` we have `m >>= (\x -> mzero) == mzero`. But it clearly fails in ```haskell undefined >>= (\x -> mzero) :: Maybe Int ``` The result is `undefined` instead of `mzero`. (Or does it mean that Maybe is broken?) Best regards, Petr

On 2013-08-18 at 20:26:23 +0200, Petr Pudlák wrote: [...]
I'd say that with `undefined` we can fail other equality laws. For example: For `MonadPlus` we have `m >>= (\x -> mzero) == mzero`. But it clearly fails in ```haskell undefined >>= (\x -> mzero) :: Maybe Int ``` The result is `undefined` instead of `mzero`. (Or does it mean that Maybe is broken?)
Btw/fyi, there was a thread "Monad laws in presence of bottoms" some time ago on haskell-cafe that seems related: http://haskell.1045720.n5.nabble.com/Monad-laws-in-presence-of-bottoms-td549... cheers, hvr

This came up elsewhere recently, so I guess I should say something.
Equality does not have anything necessarily to do with some ability to
'compare' things decidably. For instance, one can implement the computable
real numbers as functions from a precision to a rational approximation at
that precision. Given this representation, it is impossible to
algorithmically decide that two real numbers are equal; one can only decide
that two distinct numbers are not equal. However, that does not mean that a
notion of equality does not exist, or that we cannot demonstrate the
equality of two real numbers, even if we cannot decide whether two
arbitrary numbers are equal or not.
undefined is unequal to (undefined, undefined) because certain programs
will behave differently when given the two as input. This is true even
though (==) isn't one of those programs.
However, I do think there is a lot to be said toward axioms holding for
bottom being a low priority. Roughly, I care about a function's behavior on
undefined with regard to how it governs its behavior on well-defined
Haskell programs. That is, examining 'f undefined' will tell you how things
like 'fix f' will work, but I only care about the latter, not the former,
in itself. But the situation under discussion here is exactly one where we
are talking about making more programs well-defined, which I tend to think
trumps, "this fails a required equation with respect to ill-defined values."
The one thing (that I can see) that the laziness breaks is reducing things
like 'm `mappend`
mempty' to just m, and it can only break when the context in which the
expression appears requires just the tuple structure to avoid vicious
circularity. I'm not sure that's important enough for instant veto.
On Sun, Aug 18, 2013 at 2:26 PM, Petr Pudlák
Sat 17 Aug 2013 10:40:50 PM CEST, Henning Thielemann napsal:
Am 17.08.2013 22:31, schrieb Petr Pudlák:
Dear haskellers,
currently the instances are defined as
|instance (Monoid a,Monoid b) =>Monoid (a,b)where mempty = (mempty, mempty) (a1,b1) `mappend` (a2,b2) = (a1 `mappend` a2, b1 `mappend` b2)|
I think that this instance is correct, since it must hold
forall x. mappend mempty x = x
With your instance you get for x=undefined:
mappend mempty undefined = (undefined, undefined)
However, the "instance Monoid ()" is too lazy, such that it does not satisfy the identity law.
I have some doubts in this reasoning. Here `undefined` isn't a value we can compare, it represents a non-terminating program. How can we compare two non-terminating programs for equality? I'd say we can only say that two non-terminating programs are unequal, if they produce a partial results that are different. For example, `(undefined, 1)` is unequal `(undefined, 2)`. But how can we observe that `undefined` is distinct from `(undefined, undefined)`? We can't write a correctly terminating program that would observe this inequality (of course, unless we use IO and exception catching).
The only thing this additional laziness can change is to make some non-terminating programs terminating. This is very different than from having an instance that fails an equality law with defined values, in such a case we'd be able to observe some programs behave incorrectly.
I'd say that with `undefined` we can fail other equality laws. For example: For `MonadPlus` we have `m >>= (\x -> mzero) == mzero`. But it clearly fails in ```haskell undefined >>= (\x -> mzero) :: Maybe Int ``` The result is `undefined` instead of `mzero`. (Or does it mean that Maybe is broken?)
Best regards, Petr
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries

This change would spontaneously introduce space-leaks in currently
non-leaky code.
It'd be a debugging nightmare for existing users of the product Monoid
instance, of whom there are many, who would just see their code start to
throw away all their memory on newer GHC versions and have little or no
idea why, if they missed news of this update.
As a result I'm -1 on this proposal.
That said, some kind of package that provides a well-reasoned
Data.Tuple.Lazy data type could see use, as using it would imply consent to
those semantics.
I do not object morally to it, like Henning, merely pragmatically.
-Edward
On Sat, Aug 17, 2013 at 4:31 PM, Petr Pudlák
Dear haskellers,
currently the instances are defined as
instance (Monoid a, Monoid b) => Monoid (a,b) where mempty = (mempty, mempty) (a1,b1) `mappend` (a2,b2) = (a1 `mappend` a2, b1 `mappend` b2)
However for some applications this isn't lazy enough, for example
-- | Build two lists by folding on a pair of `Endo` monoids.test = head $ appEndo (fst $ foldMap (f &&& f) [1..]) [] where f = Endo . (:)
never terminates because of the unnecessary pattern matching on the constructor (,) forces evaluation of the whole infinite list.
I suggest to change all Monoid instances for tuples to be like
instance (Monoid a, Monoid b) => Monoid (a,b) where mempty = (mempty, mempty) ~(a1,b1) `mappend` ~(a2,b2) = (a1 `mappend` a2, b1 `mappend` b2)-- ^^^ ^^^
which fixes the problem.
Best regards, Petr
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I'm guessing this proposal is related to this Stack Overflow answer you gave: http://stackoverflow.com/a/18289075/1026598 Note that your solution is very similar to the solution in the `foldl` package I just released (also based off of the same blog post you got your solution from). The key differences are that: * The `foldl` solution is for left folds and uses a strict tuple internally to prevent space leaks * Your solution is for right folds and uses an extra-lazy tuple internally to promote laziness This suggests to me that it would be better to keep this extra-lazy tuple as an internal implementation detail of a right-fold package that would be the lazy analogy of `foldl`, rather than modifying the standard Haskell tuple. On 08/18/2013 01:44 PM, Edward Kmett wrote:
This change would spontaneously introduce space-leaks in currently non-leaky code.
It'd be a debugging nightmare for existing users of the product Monoid instance, of whom there are many, who would just see their code start to throw away all their memory on newer GHC versions and have little or no idea why, if they missed news of this update.
As a result I'm -1 on this proposal.
That said, some kind of package that provides a well-reasoned Data.Tuple.Lazy data type could see use, as using it would imply consent to those semantics.
I do not object morally to it, like Henning, merely pragmatically.
-Edward
On Sat, Aug 17, 2013 at 4:31 PM, Petr Pudlák
mailto:petr.mvd@gmail.com> wrote: Dear haskellers,
currently the instances are defined as
|instance (Monoid a,Monoid b) =>Monoid (a,b)where mempty = (mempty, mempty) (a1,b1) `mappend` (a2,b2) = (a1 `mappend` a2, b1 `mappend` b2)|
However for some applications this isn't lazy enough, for example
|-- | Build two lists by folding on a pair of `Endo` monoids. test = head $ appEndo (fst $ foldMap (f &&& f) [1..]) [] where f =Endo . (:)|
never terminates because of the unnecessary pattern matching on the constructor |(,)| forces evaluation of the whole infinite list.
I suggest to change all Monoid instances for tuples to be like
| instance (Monoid a,Monoid b) =>Monoid (a,b)where mempty = (mempty, mempty) ~(a1,b1) `mappend` ~(a2,b2) = (a1 `mappend` a2, b1 `mappend` b2) -- ^^^ ^^^|
which fixes the problem.
Best regards, Petr
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Am 18.08.2013 23:21, schrieb Gabriel Gonzalez:
I'm guessing this proposal is related to this Stack Overflow answer you gave:
That's a nice idea for a fundamental problem. How about generalizing 'fold' to Foldable types?

Thank you all for the responses. Edward's objection is very serious, I didn't think of it. Because of it I retract the proposal, this would indeed create big problems. (I just wish someone invents an oracle strictness analyzer...) Instead, as suggested, I'll make a package with `newtype` wrappers for tuples that will provide the extra-lazy monoid semantics. Any ideas for what other type classes except `Monoid` (and `Semigroup`) could be included? Or perhaps even other data types except tuples? Dne 08/18/2013 11:21 PM, Gabriel Gonzalez napsal(a):
I'm guessing this proposal is related to this Stack Overflow answer you gave:
http://stackoverflow.com/a/18289075/1026598
Note that your solution is very similar to the solution in the `foldl` package I just released (also based off of the same blog post you got your solution from). The key differences are that:
* The `foldl` solution is for left folds and uses a strict tuple internally to prevent space leaks * Your solution is for right folds and uses an extra-lazy tuple internally to promote laziness
This suggests to me that it would be better to keep this extra-lazy tuple as an internal implementation detail of a right-fold package that would be the lazy analogy of `foldl`, rather than modifying the standard Haskell tuple. Yes, this is how I encountered the problem. If I have time I'll make a mirror package `foldr` based on extra-lazy tuples. (Or perhaps we could merge the ideas into a single package.)
Best regards, Petr

If you are looking into a tackling lazy foldr, I'd recommend also including
or considering using foldMap as a basis. It can make an asymptotic
difference for some folds. I sent Gabriel a version in that style. I'll dig
up a copy and send it your way as well.
-Edward
On Mon, Aug 19, 2013 at 3:29 AM, Petr Pudlák
Thank you all for the responses.
Edward's objection is very serious, I didn't think of it. Because of it I retract the proposal, this would indeed create big problems. (I just wish someone invents an oracle strictness analyzer...)
Instead, as suggested, I'll make a package with `newtype` wrappers for tuples that will provide the extra-lazy monoid semantics. Any ideas for what other type classes except `Monoid` (and `Semigroup`) could be included? Or perhaps even other data types except tuples?
Dne 08/18/2013 11:21 PM, Gabriel Gonzalez napsal(a):
I'm guessing this proposal is related to this Stack Overflow answer you gave:
http://stackoverflow.com/a/18289075/1026598
Note that your solution is very similar to the solution in the `foldl` package I just released (also based off of the same blog post you got your solution from). The key differences are that:
* The `foldl` solution is for left folds and uses a strict tuple internally to prevent space leaks * Your solution is for right folds and uses an extra-lazy tuple internally to promote laziness
This suggests to me that it would be better to keep this extra-lazy tuple as an internal implementation detail of a right-fold package that would be the lazy analogy of `foldl`, rather than modifying the standard Haskell tuple.
Yes, this is how I encountered the problem. If I have time I'll make a mirror package `foldr` based on extra-lazy tuples. (Or perhaps we could merge the ideas into a single package.)
Best regards, Petr

This is exactly how I run into the Monoid problem. My original `foldr` version works fine, but when I saw this Gabriel's post: http://www.haskellforall.com/2013/08/composable-streaming-folds.html the monoid variant looked cleaner and nicer so I wanted to redesign my idea using monoids as well. And that was precisely when I realized that (,) isn't lazy enough. Could you elaborate a bit when/how the asymptotic difference occurs? Best regards, Petr Dne 08/19/2013 02:03 PM, Edward Kmett napsal(a):
If you are looking into a tackling lazy foldr, I'd recommend also including or considering using foldMap as a basis. It can make an asymptotic difference for some folds. I sent Gabriel a version in that style. I'll dig up a copy and send it your way as well.
-Edward
On Mon, Aug 19, 2013 at 3:29 AM, Petr Pudlák
mailto:petr.mvd@gmail.com> wrote: Thank you all for the responses.
Edward's objection is very serious, I didn't think of it. Because of it I retract the proposal, this would indeed create big problems. (I just wish someone invents an oracle strictness analyzer...)
Instead, as suggested, I'll make a package with `newtype` wrappers for tuples that will provide the extra-lazy monoid semantics. Any ideas for what other type classes except `Monoid` (and `Semigroup`) could be included? Or perhaps even other data types except tuples?
Dne 08/18/2013 11:21 PM, Gabriel Gonzalez napsal(a):
I'm guessing this proposal is related to this Stack Overflow answer you gave:
http://stackoverflow.com/a/18289075/1026598
Note that your solution is very similar to the solution in the `foldl` package I just released (also based off of the same blog post you got your solution from). The key differences are that:
* The `foldl` solution is for left folds and uses a strict tuple internally to prevent space leaks * Your solution is for right folds and uses an extra-lazy tuple internally to promote laziness
This suggests to me that it would be better to keep this extra-lazy tuple as an internal implementation detail of a right-fold package that would be the lazy analogy of `foldl`, rather than modifying the standard Haskell tuple.
Yes, this is how I encountered the problem. If I have time I'll make a mirror package `foldr` based on extra-lazy tuples. (Or perhaps we could merge the ideas into a single package.)
Best regards, Petr

With foldMap one can have structures that get to explicitly reuse previous
intermediate results.
e.g.
http://hackage.haskell.org/packages/archive/compressed/3.0.3/doc/html/Data-C...
you a list with a more efficient fold by using LZ78 to identify
sharing with earlier parts of the list.
With foldr you can't exploit such regularity as you can merely append one
element at a time.
Less drastically, with foldMap, you can binary search a tree structure if
the foldMap preserves the original associativity of the structure.
The lens package uses this to navigate to keys in a Zipper over a Map to a
given key in O(log n) time borrowing the asymptotics from the balance of
the underlying structure.
In my current work I'm using "sequence-algebras" and "sequence-trees" to
exploit even more structure than foldMap gives me.
I'll probably write up an article at some point soon on the School of
Haskell.
-Edward
On Mon, Aug 19, 2013 at 9:31 AM, Petr Pudlák
This is exactly how I run into the Monoid problem. My original `foldr` version works fine, but when I saw this Gabriel's post: http://www.haskellforall.com/2013/08/composable-streaming-folds.html the monoid variant looked cleaner and nicer so I wanted to redesign my idea using monoids as well. And that was precisely when I realized that (,) isn't lazy enough.
Could you elaborate a bit when/how the asymptotic difference occurs?
Best regards, Petr
Dne 08/19/2013 02:03 PM, Edward Kmett napsal(a):
If you are looking into a tackling lazy foldr, I'd recommend also including or considering using foldMap as a basis. It can make an asymptotic difference for some folds. I sent Gabriel a version in that style. I'll dig up a copy and send it your way as well.
-Edward
On Mon, Aug 19, 2013 at 3:29 AM, Petr Pudlák
wrote: Thank you all for the responses.
Edward's objection is very serious, I didn't think of it. Because of it I retract the proposal, this would indeed create big problems. (I just wish someone invents an oracle strictness analyzer...)
Instead, as suggested, I'll make a package with `newtype` wrappers for tuples that will provide the extra-lazy monoid semantics. Any ideas for what other type classes except `Monoid` (and `Semigroup`) could be included? Or perhaps even other data types except tuples?
Dne 08/18/2013 11:21 PM, Gabriel Gonzalez napsal(a):
I'm guessing this proposal is related to this Stack Overflow answer you gave:
http://stackoverflow.com/a/18289075/1026598
Note that your solution is very similar to the solution in the `foldl` package I just released (also based off of the same blog post you got your solution from). The key differences are that:
* The `foldl` solution is for left folds and uses a strict tuple internally to prevent space leaks * Your solution is for right folds and uses an extra-lazy tuple internally to promote laziness
This suggests to me that it would be better to keep this extra-lazy tuple as an internal implementation detail of a right-fold package that would be the lazy analogy of `foldl`, rather than modifying the standard Haskell tuple.
Yes, this is how I encountered the problem. If I have time I'll make a mirror package `foldr` based on extra-lazy tuples. (Or perhaps we could merge the ideas into a single package.)
Best regards, Petr

Just to be sure that I understand it correctly: If I take foldMap as the basis and I run it on a binary tree with First/Last monoids, I get both result in O(depth). But if I take foldl or foldr as the basis, either searching for the first or for the last element will take O(size), am I right? Dne 08/19/2013 04:14 PM, Edward Kmett napsal(a):
With foldMap one can have structures that get to explicitly reuse previous intermediate results.
e.g. http://hackage.haskell.org/packages/archive/compressed/3.0.3/doc/html/Data-C... gives you a list with a more efficient fold by using LZ78 to identify sharing with earlier parts of the list.
With foldr you can't exploit such regularity as you can merely append one element at a time.
Less drastically, with foldMap, you can binary search a tree structure if the foldMap preserves the original associativity of the structure.
The lens package uses this to navigate to keys in a Zipper over a Map to a given key in O(log n) time borrowing the asymptotics from the balance of the underlying structure.
In my current work I'm using "sequence-algebras" and "sequence-trees" to exploit even more structure than foldMap gives me.
I'll probably write up an article at some point soon on the School of Haskell.
-Edward
On Mon, Aug 19, 2013 at 9:31 AM, Petr Pudlák
mailto:petr.mvd@gmail.com> wrote: This is exactly how I run into the Monoid problem. My original `foldr` version works fine, but when I saw this Gabriel's post: http://www.haskellforall.com/2013/08/composable-streaming-folds.html the monoid variant looked cleaner and nicer so I wanted to redesign my idea using monoids as well. And that was precisely when I realized that (,) isn't lazy enough.
Could you elaborate a bit when/how the asymptotic difference occurs?
Best regards, Petr
Dne 08/19/2013 02:03 PM, Edward Kmett napsal(a):
If you are looking into a tackling lazy foldr, I'd recommend also including or considering using foldMap as a basis. It can make an asymptotic difference for some folds. I sent Gabriel a version in that style. I'll dig up a copy and send it your way as well.
-Edward
On Mon, Aug 19, 2013 at 3:29 AM, Petr Pudlák
mailto:petr.mvd@gmail.com> wrote: Thank you all for the responses.
Edward's objection is very serious, I didn't think of it. Because of it I retract the proposal, this would indeed create big problems. (I just wish someone invents an oracle strictness analyzer...)
Instead, as suggested, I'll make a package with `newtype` wrappers for tuples that will provide the extra-lazy monoid semantics. Any ideas for what other type classes except `Monoid` (and `Semigroup`) could be included? Or perhaps even other data types except tuples?
Dne 08/18/2013 11:21 PM, Gabriel Gonzalez napsal(a):
I'm guessing this proposal is related to this Stack Overflow answer you gave:
http://stackoverflow.com/a/18289075/1026598
Note that your solution is very similar to the solution in the `foldl` package I just released (also based off of the same blog post you got your solution from). The key differences are that:
* The `foldl` solution is for left folds and uses a strict tuple internally to prevent space leaks * Your solution is for right folds and uses an extra-lazy tuple internally to promote laziness
This suggests to me that it would be better to keep this extra-lazy tuple as an internal implementation detail of a right-fold package that would be the lazy analogy of `foldl`, rather than modifying the standard Haskell tuple.
Yes, this is how I encountered the problem. If I have time I'll make a mirror package `foldr` based on extra-lazy tuples. (Or perhaps we could merge the ideas into a single package.)
Best regards, Petr

Yep.I should have reached for the easier examples. :)
Sent from my iPad
On Aug 19, 2013, at 10:47 AM, Petr Pudlák
Just to be sure that I understand it correctly: If I take foldMap as the basis and I run it on a binary tree with First/Last monoids, I get both result in O(depth). But if I take foldl or foldr as the basis, either searching for the first or for the last element will take O(size), am I right?
Dne 08/19/2013 04:14 PM, Edward Kmett napsal(a):
With foldMap one can have structures that get to explicitly reuse previous intermediate results.
e.g. http://hackage.haskell.org/packages/archive/compressed/3.0.3/doc/html/Data-C... gives you a list with a more efficient fold by using LZ78 to identify sharing with earlier parts of the list.
With foldr you can't exploit such regularity as you can merely append one element at a time.
Less drastically, with foldMap, you can binary search a tree structure if the foldMap preserves the original associativity of the structure.
The lens package uses this to navigate to keys in a Zipper over a Map to a given key in O(log n) time borrowing the asymptotics from the balance of the underlying structure.
In my current work I'm using "sequence-algebras" and "sequence-trees" to exploit even more structure than foldMap gives me.
I'll probably write up an article at some point soon on the School of Haskell.
-Edward
On Mon, Aug 19, 2013 at 9:31 AM, Petr Pudlák
wrote: This is exactly how I run into the Monoid problem. My original `foldr` version works fine, but when I saw this Gabriel's post: http://www.haskellforall.com/2013/08/composable-streaming-folds.html the monoid variant looked cleaner and nicer so I wanted to redesign my idea using monoids as well. And that was precisely when I realized that (,) isn't lazy enough.
Could you elaborate a bit when/how the asymptotic difference occurs?
Best regards, Petr
Dne 08/19/2013 02:03 PM, Edward Kmett napsal(a):
If you are looking into a tackling lazy foldr, I'd recommend also including or considering using foldMap as a basis. It can make an asymptotic difference for some folds. I sent Gabriel a version in that style. I'll dig up a copy and send it your way as well.
-Edward
On Mon, Aug 19, 2013 at 3:29 AM, Petr Pudlák
wrote: Thank you all for the responses.
Edward's objection is very serious, I didn't think of it. Because of it I retract the proposal, this would indeed create big problems. (I just wish someone invents an oracle strictness analyzer...)
Instead, as suggested, I'll make a package with `newtype` wrappers for tuples that will provide the extra-lazy monoid semantics. Any ideas for what other type classes except `Monoid` (and `Semigroup`) could be included? Or perhaps even other data types except tuples?
Dne 08/18/2013 11:21 PM, Gabriel Gonzalez napsal(a):
I'm guessing this proposal is related to this Stack Overflow answer you gave:
http://stackoverflow.com/a/18289075/1026598
Note that your solution is very similar to the solution in the `foldl` package I just released (also based off of the same blog post you got your solution from). The key differences are that:
* The `foldl` solution is for left folds and uses a strict tuple internally to prevent space leaks * Your solution is for right folds and uses an extra-lazy tuple internally to promote laziness
This suggests to me that it would be better to keep this extra-lazy tuple as an internal implementation detail of a right-fold package that would be the lazy analogy of `foldl`, rather than modifying the standard Haskell tuple. Yes, this is how I encountered the problem. If I have time I'll make a mirror package `foldr` based on extra-lazy tuples. (Or perhaps we could merge the ideas into a single package.)
Best regards, Petr

Edward Kmett
writes:
As a result I'm -1 on this proposal.
That said, some kind of package that provides a well-reasoned Data.Tuple.Lazy data type could see use, as using it would imply consent to those semantics.
-1 to changing the product tuple instance, and +1 to moving those semantics into Data.Tuple.Lazy. -- John Wiegley FP Complete Haskell tools, training and consulting http://fpcomplete.com johnw on #haskell/irc.freenode.net
participants (7)
-
Dan Doel
-
Edward Kmett
-
Gabriel Gonzalez
-
Henning Thielemann
-
Herbert Valerio Riedel
-
John Wiegley
-
Petr Pudlák