Textbook example of instance Foldable ((,) a)

Dear Cafe - you might find this entertaining: an error in my code that cost me some hours (most Pictures are equal?) until I finally realized instance Eq a => Eq (Picture a) where p == q = dim p == dim q - && all (\ i -> contents p i == contents q i) (bounds p) + && all (\ i -> contents p i == contents q i) (A.range $ bounds p) Henning already called this "Matlab league" behaviour, https://mail.haskell.org/pipermail/libraries/2016-February/026678.html Well it's just a fun observation now, I am not implying anything. Enjoy! - J. Link to full source: https://gitlab.imn.htwk-leipzig.de/autotool/all0/-/issues/660#note_24567

Am Mo., 23. Nov. 2020 um 14:54 Uhr schrieb Johannes Waldmann < johannes.waldmann@htwk-leipzig.de>:
[...] Henning already called this "Matlab league" behaviour, https://mail.haskell.org/pipermail/libraries/2016-February/026678.html
Well it's just a fun observation now, I am not implying anything. Enjoy!
There was a mega-thread in March/April 2017 about adding even more of this nonsense... :-D https://mail.haskell.org/pipermail/libraries/2017-March/027824.html Luckily enough, there was no consensus.

>>>>> "SP" == Sven Panne

On Mon, 23 Nov 2020, Manuel Schneckenreither wrote:
"SP" == Sven Panne
writes: SP> Am Mo., 23. Nov. 2020 um 14:54 Uhr schrieb Johannes Waldmann SP>
: [...] Henning already SP> called this "Matlab league" behaviour, SP> https://mail.haskell.org/pipermail/libraries/2016-February/026678.html What is the intiutive way of implementing the tuple instance like this [1]
instance Foldable ((,) a) where .. length _ = 1 ..
I cannot come up with a real argument, except to say there is something.
"length (a,b) == 1" is only a consequence of defining instance Foldable for pairs. It was not the argument to implement that instance, at all.

>>>>> "HT" == Henning Thielemann

The expectation that length = getSum . foldMap (Sum . const 1) On Mon, Nov 23, 2020, 10:21 AM Manuel Schneckenreither < manuel.schnecki@gmail.com> wrote:
>>>>> "HT" == Henning Thielemann
writes: HT> "length (a,b) == 1" is only a consequence of defining instance HT> Foldable for pairs. It was not the argument to implement that HT> instance, at all.
What was the argument to use 1, not 2 for instance? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

length is part of the Foldable class: length = foldl' https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... (\c https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... _ -> c https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... + https://hackage.haskell.org/package/base-4.14.0.0/docs/src/GHC.Num.html#%2B 1) 0 It is probably defined this way s.t. it satisfies: length = length . toList Not the actual definition, but you can read toList as: toList = foldr (:) [] So as soon as one defines foldr for pairs: foldr https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... f https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... z https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... (_, y https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm...) = f https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... y https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... z https://hackage.haskell.org/package/base-4.14.0.0/docs/src/Data.Foldable.htm... We get: toList (a,b) = [b] Using the 'natural' property: length = length . toList We obtain: length (a,b) = length [b] = 1 On Mon, Nov 23, 2020 at 10:22 AM Manuel Schneckenreither < manuel.schnecki@gmail.com> wrote:
>>>>> "HT" == Henning Thielemann
writes: HT> "length (a,b) == 1" is only a consequence of defining instance HT> Foldable for pairs. It was not the argument to implement that HT> instance, at all.
What was the argument to use 1, not 2 for instance? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Am Mo., 23. Nov. 2020 um 16:32 Uhr schrieb Sebastiaan Joosten < sjcjoosten+haskell@gmail.com>:
[...] We obtain: length (a,b) = length [b] = 1
Quoting my former self ( https://mail.haskell.org/pipermail/libraries/2017-April/027905.html), you get even more "fun" stuff with lots of potential for late-night debugging hours: maximum (3,2) => 2 minimum (4,5) => 5 sum (6,7) => 7 product (8,9) => 9 Yes, you can think of (X, Y) as "Y with context X" or "a one-element container with Y in it", but is this really what comes to your mind first? I still highly doubt that. The Foldable-Traversable-in-Prelude change was largely a good thing, but very surprising (and not really needed) changes coming stealthily with it were only communicated when it was already too late... :-/

So what should maximum (2, "potato") be?
On Mon, Nov 23, 2020, 14:19 Sven Panne
Am Mo., 23. Nov. 2020 um 16:32 Uhr schrieb Sebastiaan Joosten < sjcjoosten+haskell@gmail.com>:
[...] We obtain: length (a,b) = length [b] = 1
Quoting my former self ( https://mail.haskell.org/pipermail/libraries/2017-April/027905.html), you get even more "fun" stuff with lots of potential for late-night debugging hours:
maximum (3,2) => 2 minimum (4,5) => 5 sum (6,7) => 7 product (8,9) => 9
Yes, you can think of (X, Y) as "Y with context X" or "a one-element container with Y in it", but is this really what comes to your mind first? I still highly doubt that. The Foldable-Traversable-in-Prelude change was largely a good thing, but very surprising (and not really needed) changes coming stealthily with it were only communicated when it was already too late... :-/
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Mon, Nov 23, 2020 at 09:54:26PM +0100, Francesco Ariis wrote:
Il 23 novembre 2020 alle 14:40 Zemyla ha scritto:
So what should maximum (2, "potato") be?
For people who did not agree with `instance Foldable (,) a`, a type error!
Which of the following would they give up? A. Foldable as superclass of Traversable B. (a,) as Traversable Personally I think in retrospect I think I'd give up both and use explicit Traversals (i.e. optics instead). That way one would have to write allOf each (\ i -> contents p i == contents q i) ... By contrast allOf _2 (\ i -> contents p i == contents q i) ... obviously looks wrong. Tom

On Mon, 23 Nov 2020, Tom Ellis wrote:
On Mon, Nov 23, 2020 at 09:54:26PM +0100, Francesco Ariis wrote:
Il 23 novembre 2020 alle 14:40 Zemyla ha scritto:
So what should maximum (2, "potato") be?
For people who did not agree with `instance Foldable (,) a`, a type error!
Which of the following would they give up?
A. Foldable as superclass of Traversable
B. (a,) as Traversable
Personally I think in retrospect I think I'd give up both
You cannot really give up A, because Foldable methods can be implemented in terms of traverse.

>>>>> "TE" == Tom Ellis
On Mon, Nov 23, 2020 at 09:54:26PM +0100, Francesco Ariis wrote:
Il 23 novembre 2020 alle 14:40 Zemyla ha scritto:
So what should maximum (2, "potato") be?
For people who did not agree with `instance Foldable (,) a`, a type error!
Which of the following would they give up?
A. Foldable as superclass of Traversable
B. (a,) as Traversable
Personally I think in retrospect I think I'd give up both and use explicit Traversals (i.e. optics instead). That way one would have to write
allOf each (\ i -> contents p i == contents q i) ...
By contrast
allOf _2 (\ i -> contents p i == contents q i) ...
obviously looks wrong.
Tom _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

In homage to the ironic phrase "It's technically true, which is the best
kind of true," perhaps we need a superclass TechnicallyFoldable. :D Then
(,) a could be an instance of TechnicallyFoldable but not Foldable ,
tlength could be defined as tlength = length for (Foldable a =>
TechnicallyFoldable a), and anybody who really wants the maximally general
option could always use tlength.
The parallel with fmap speaks for itself. :)
Den tis 24 nov. 2020 11:56Manuel Schneckenreither
>>>>> "TE" == Tom Ellis
writes: TE> On Mon, Nov 23, 2020 at 09:54:26PM +0100, Francesco Ariis wrote:
TE> Which of the following would they give up?
TE> A. Foldable as superclass of Traversable
TE> B. (a,) as Traversable
For me it is B. Even the Foldable hackage description states "Functors representing data structures that can be traversed from left to right." The tuple is however not traversed from left to right, but solely on the right (as it's half filled).
For me it doesn't make sense to implement it, just because it's implementable. I think the current implementation does not add more value than it harms.
El lun., 23 nov. 2020 22:23, Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> escribió:
On Mon, Nov 23, 2020 at 09:54:26PM +0100, Francesco Ariis wrote:
Il 23 novembre 2020 alle 14:40 Zemyla ha scritto:
So what should maximum (2, "potato") be?
For people who did not agree with `instance Foldable (,) a`, a type error!
Which of the following would they give up?
A. Foldable as superclass of Traversable
B. (a,) as Traversable
Personally I think in retrospect I think I'd give up both and use explicit Traversals (i.e. optics instead). That way one would have to write
allOf each (\ i -> contents p i == contents q i) ...
By contrast
allOf _2 (\ i -> contents p i == contents q i) ...
obviously looks wrong.
Tom _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Il 23 novembre 2020 alle 21:18 Sven Panne ha scritto:
Yes, you can think of (X, Y) as "Y with context X" or "a one-element container with Y in it", but is this really what comes to your mind first? I still highly doubt that. The Foldable-Traversable-in-Prelude change was largely a good thing, but very surprising (and not really needed) changes coming stealthily with it were only communicated when it was already too late... :-/
I recall a long thread, with everyone top posting. This feature could have helped OP: https://gitlab.haskell.org/ghc/ghc/-/issues/11796 but unfortunately is still in design stage —F

On Mon, Nov 23, 2020 at 09:45:55PM +0100, Francesco Ariis wrote:
Il 23 novembre 2020 alle 21:18 Sven Panne ha scritto:
Yes, you can think of (X, Y) as "Y with context X" or "a one-element container with Y in it", but is this really what comes to your mind first? I still highly doubt that. The Foldable-Traversable-in-Prelude change was largely a good thing, but very surprising (and not really needed) changes coming stealthily with it were only communicated when it was already too late... :-/
I recall a long thread, with everyone top posting. This feature could have helped OP:
https://gitlab.haskell.org/ghc/ghc/-/issues/11796
but unfortunately is still in design stage
Fwiw there is at least some strong user interest in this feature if anyone is thinking of working on it. I find myself checking on its progress pretty often, and would use it in our production codebase in a heartbeat. The strongest motivation is bugs that I've caught during a refactor, where a type somewhere changes from e.g. [x] to (y, [x]), and deep in some function a call to length/maximum/whatever just starts returning useless values without a type error. Consider, for example: do x <- getValuesForId "foo" when (length x > 1) $ fail "Unlikely condition: more than one value returned" ... It may be a long time before you discover the 'when' clause will never fire because the type of x has changed to a 2-tuple. In the meantime, you've been doing something wrong with your conflicting data. Tom

On Tue, Nov 24, 2020 at 02:13:56AM -0500, amindfv--- via Haskell-Cafe wrote:
Fwiw there is at least some strong user interest in this feature if anyone is thinking of working on it. I find myself checking on its progress pretty often, and would use it in our production codebase in a heartbeat.
Rather than waiting, it is perhaps more pragmatic to go with a custom Prelude, which one can have now, even for versions of GHC/base, that won't have the feature in question: {-# LANGUAGE NoImplicitPrelude #-} module Main (main) where import ListPrelude import qualified Data.Foldable as F main :: IO () main = do let { one, two :: Int; one = 1; two = 2 } -- OK print $ length [one, two] print $ F.length (one, two) -- Type error -- print $ length (one, two) -- Viktor.

On Tue, 24 Nov 2020, Viktor Dukhovni wrote:
Rather than waiting, it is perhaps more pragmatic to go with a custom Prelude, which one can have now, even for versions of GHC/base, that won't have the feature in question:
I have such a Prelude: https://hackage.haskell.org/package/prelude-compat It helps a bit, but does not fully solve the problem. If you use Fold.all on a Map and then switch from Map k a to (Map k a, b) you will again not encounter a warning nor a type error. I had the idea of implementing forbidden instances like: instance Unsatisfiable a => Foldable ((,) a) where If I use them (or import them?) they would conflict with the one from FTP-Prelude. I have not tried that idea. It might exclude importing code that uses Foldable on pair intentionally.

On Tue, Nov 24, 2020 at 10:20:58AM +0100, Henning Thielemann wrote:
Rather than waiting, it is perhaps more pragmatic to go with a custom Prelude, which one can have now, even for versions of GHC/base, that won't have the feature in question:
I have such a Prelude: https://hackage.haskell.org/package/prelude-compat
It helps a bit, but does not fully solve the problem.
If you use Fold.all on a Map and then switch from Map k a to (Map k a, b) you will again not encounter a warning nor a type error.
Yes, for that one might have to be disciplined and use a monomorphised variant: allMapValues :: (a -> Bool) -> Map k a -> Bool allMapValues = Data.Foldable.all although the risk is only present when (a ~ b), or the predicate is sufficiently polymorphic (over some superclass of `a` and `b`). And of course, when refactoring, instead of moving to a 2-tuple, that brings in possibly unwanted instances, one can instead choose a custom product type, that does not have a Foldable instance: -- coercible to a 2-tuple if/as needed newtype T2 a b = T2 { _unT2 :: (a, b) } deriving (Eq, Ord, Show) to give one's 2-tuples exactly the desired instances and no more. This admittedly is not terribly ergonomic. -- Viktor.

On Tue, 24 Nov 2020, Viktor Dukhovni wrote:
And of course, when refactoring, instead of moving to a 2-tuple, that brings in possibly unwanted instances, one can instead choose a custom product type, that does not have a Foldable instance:
-- coercible to a 2-tuple if/as needed newtype T2 a b = T2 { _unT2 :: (a, b) } deriving (Eq, Ord, Show)
to give one's 2-tuples exactly the desired instances and no more. This admittedly is not terribly ergonomic.
If people would use custom pair types we would not need Foldable on pairs, at all.

On 2020-11-23 10:30 -0500, Sebastiaan Joosten wrote:
length is part of the Foldable class:
length = foldl' (\c _ -> c+1) 0 It is probably defined this way s.t. it satisfies: length = length . toList Not the actual definition, but you can read toList as: toList = foldr (:) []
So as soon as one defines foldr for pairs:
foldr f z (_, y) = f y z
We get: toList (a,b) = [b]
Using the 'natural' property: length = length . toList We obtain: length (a,b) = length [b] = 1
On Mon, Nov 23, 2020 at 10:22 AM Manuel Schneckenreither < manuel.schnecki@gmail.com> wrote:
>>>>> "HT" == Henning Thielemann
writes: HT> "length (a,b) == 1" is only a consequence of defining instance HT> Foldable for pairs. It was not the argument to implement that HT> instance, at all.
What was the argument to use 1, not 2 for instance?
ok, but why define foldr like that? A long time ago, I saw an exposition of lists in an imperative setting which treated them as pairs of (value, pointer) where the pointer pointed to the next item. If we start with the above folder for pairs, I think we wouldn't get the usual foldr on lists defined in this way from pairs, no? Ok, I see, pairs are used for lots of things, including lists. They could also be used as the basis for longer tuples. Another suggestion, why don't we define foldr via currying: foldr f z (x,y) = f z x y ?
participants (14)
-
amindfv@mailbox.org
-
Bryan Richter
-
David Feuer
-
Francesco Ariis
-
Henning Thielemann
-
Johannes Waldmann
-
John Beattie
-
Manuel Schneckenreither
-
Sebastiaan Joosten
-
Sven Panne
-
Tom Ellis
-
Tony Morris
-
Viktor Dukhovni
-
Zemyla