
Friends, I address you this evening in the desperate hope that, though we have become divided by harsh words, we may come together again as one family in Haskell. Before, we saw as through a glass, darkly. To drive back the night, we stoked the fires of our passion. Now the heat burns us! The smoke stings our eyes! I intend to magnify what was hidden so we may see clearly by only a small flame. We came to Haskell along many paths, but the same values drew us all. One of the values dearest to us is the ability to reason statically about our programs. To enhance this ability which Haskell naturally affords us, we have devised laws to govern our type classes. Type class laws are rightly judged by their strength: the ways in which they constrain the instances we may write. When these laws bind us most tightly, we may reason most freely. With this in mind, let us turn to the Foldable class. Foldable has several laws, but I will focus on two. First, for foldr and foldMap,
foldr f z t = appEndo (foldMap (Endo . f) t) z
Second, optionally, for Functors,
foldMap f = fold . fmap f
There are other laws, but for my purposes, they essentially follow from the above. It is generally acknowledged that these laws are relatively weak: it is difficult to conceive an instance which violates them that is not an egregious violation. With that, I offer the following simple proposal. I doubt it will achieve consensus, but I believe it will illuminate our positions more clearly. I hope it allows us to see each other with more empathy. SAFE - Stronger Alternative Foldable Enhancement / Elucidation Foldable will gain a superclass, Alternative:
class Alternative t => Foldable t where { ... }
The members of the class will not change. The class will gain the following laws to supercede the existing laws:
foldMap f empty = mempty foldMap f (xs <|> ys) = foldMap f xs <> foldMap f ys
foldr f z empty = z foldr f z (xs <|> ys) = foldr f (foldr f z ys) xs
The laws for the other members follow in the obvious way. Some instances from base are ruled out: Identity, Either a, (,) a, Proxy, and Const m. Implementing this change would necessitate attaching warnings to those instances for the customary length of time. It is my understanding that GHC is not currently able to attach warnings to instances, but I think that would be a useful feature to add, even absent the current proposal. I think this Foldable class is better than the one we have now. These constraints are stronger because they show the connection between Alternative and Monoid. I will pause here a moment because I think this is crucial to the contention between us. Foldable could be a bridge between Alternative and Monoid. We do not agree about how much may be expected of the Foldable class. I think this is what we should expect. I think this guarantee, that there is a monoidal or Alternative structure underlying Foldable, was always the unarticulated vision behind the objections to these contentious instances. I hope that the utility and elegance of my proposal will convince you, but failing that I hope it illuminates what should be our topic of discussion: not "What is to be done about Foldable?" but rather, "What is to be expected of Foldable?" Sincerely, Thomas

This sounds appealing until one realizes that Alternative doesn’t just rule out _some_ but _nearly all_ the things we may want to be Foldable. Especially so since Alternative is a subclass of Applicative. And since Foldable is a superclass of Traversable, it rules out a good degree of the things we want to be Traversable. For example, Set is a very good example of something we want to be Foldable. But it can’t be made an Alternative. Something we want to traverse often (and fold sometimes) is Map. Map is not something that can be made an Alternative either. Another example: Maybe is something that _is_ an Alternative. But it cannot be made Foldable under this set of laws, since it would fail them. In fact, all alternative instances that have a “choice-like” rather than “concat-like” <|> would fail this law. And alternative instances are rare enough as is. ¯\_(ツ)_/¯ —Gershom On February 24, 2016 at 11:04:33 PM, Thomas Tuegel (ttuegel@gmail.com) wrote:
Friends,
I address you this evening in the desperate hope that, though we have become divided by harsh words, we may come together again as one family in Haskell. Before, we saw as through a glass, darkly. To drive back the night, we stoked the fires of our passion. Now the heat burns us! The smoke stings our eyes!
I intend to magnify what was hidden so we may see clearly by only a small flame.
We came to Haskell along many paths, but the same values drew us all. One of the values dearest to us is the ability to reason statically about our programs. To enhance this ability which Haskell naturally affords us, we have devised laws to govern our type classes. Type class laws are rightly judged by their strength: the ways in which they constrain the instances we may write. When these laws bind us most tightly, we may reason most freely.
With this in mind, let us turn to the Foldable class. Foldable has several laws, but I will focus on two. First, for foldr and foldMap,
foldr f z t = appEndo (foldMap (Endo . f) t) z
Second, optionally, for Functors,
foldMap f = fold . fmap f
There are other laws, but for my purposes, they essentially follow from the above. It is generally acknowledged that these laws are relatively weak: it is difficult to conceive an instance which violates them that is not an egregious violation.
With that, I offer the following simple proposal. I doubt it will achieve consensus, but I believe it will illuminate our positions more clearly. I hope it allows us to see each other with more empathy.
SAFE - Stronger Alternative Foldable Enhancement / Elucidation
Foldable will gain a superclass, Alternative:
class Alternative t => Foldable t where { ... }
The members of the class will not change. The class will gain the following laws to supercede the existing laws:
foldMap f empty = mempty foldMap f (xs <|> ys) = foldMap f xs <> foldMap f ys
foldr f z empty = z foldr f z (xs <|> ys) = foldr f (foldr f z ys) xs
The laws for the other members follow in the obvious way. Some instances from base are ruled out: Identity, Either a, (,) a, Proxy, and Const m. Implementing this change would necessitate attaching warnings to those instances for the customary length of time. It is my understanding that GHC is not currently able to attach warnings to instances, but I think that would be a useful feature to add, even absent the current proposal.
I think this Foldable class is better than the one we have now. These constraints are stronger because they show the connection between Alternative and Monoid.
I will pause here a moment because I think this is crucial to the contention between us. Foldable could be a bridge between Alternative and Monoid. We do not agree about how much may be expected of the Foldable class. I think this is what we should expect. I think this guarantee, that there is a monoidal or Alternative structure underlying Foldable, was always the unarticulated vision behind the objections to these contentious instances.
I hope that the utility and elegance of my proposal will convince you, but failing that I hope it illuminates what should be our topic of discussion: not "What is to be done about Foldable?" but rather, "What is to be expected of Foldable?"
Sincerely, Thomas _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Gershom,
Thank you for taking the time to write such a thoughtful response. I appreciate
that you gave concrete examples; I think the discussion will be more meaningful
for it.
On Wed, Feb 24, 2016 at 10:34 PM, Gershom B
This sounds appealing until one realizes that Alternative doesn't just rule out _some_ but _nearly all_ the things we may want to be Foldable. Especially so since Alternative is a subclass of Applicative.
And since Foldable is a superclass of Traversable, it rules out a good degree of the things we want to be Traversable.
This is a radical position, but I don't think we do want these things to be Traversable or Foldable. Let me explain.
For example, Set is a very good example of something we want to be Foldable. But it can't be made an Alternative.
Foldable implies a notion of structural direction through the associativity of its members. Set is different from the well-behaved Foldables because its notion of direction or order is not structural, i.e. not preserved by operations on Set.
Something we want to traverse often (and fold sometimes) is Map. Map is not something that can be made an Alternative either.
Because it is not Applicative? Yes. For the same reason as Set, though, I do not think it should be Foldable or Traversable. It is convenient, but unsound. Or at least, less-sound. To fold or traverse Set and Map, I think the sound thing to do is to use one of the provided functions to convert them to a type where ordering is reflected structurally.
Another example: Maybe is something that _is_ an Alternative.
But it cannot be made Foldable under this set of laws, since it would fail them. In fact, all alternative instances that have a "choice-like" rather than "concat-like" <|> would fail this law. And alternative instances are rare enough as is.
Yes, exactly. I am suggesting we curtail the scope of Foldable severely in order to expand its power vastly. Regards, Tom

Thomas Tuegel
And since Foldable is a superclass of Traversable, it rules out a good degree of the things we want to be Traversable.
This is a radical position, but I don't think we do want these things to be Traversable or Foldable. Let me explain.
For example, Set is a very good example of something we want to be Foldable. But it can't be made an Alternative.
Foldable implies a notion of structural direction through the associativity of its members. Set is different from the well-behaved Foldables because its notion of direction or order is not structural, i.e. not preserved by operations on Set.
Something we want to traverse often (and fold sometimes) is Map. Map is not something that can be made an Alternative either.
Because it is not Applicative? Yes. For the same reason as Set, though, I do not think it should be Foldable or Traversable. It is convenient, but unsound. Or at least, less-sound. To fold or traverse Set and Map, I think the sound thing to do is to use one of the provided functions to convert them to a type where ordering is reflected structurally.
What about adding unstructural fold/traversal under different names? That way we could have the convenience when we truly don't care about the directionality property, and the benefits of pure folding at the same time. -- с уважениeм / respectfully, Косырев Сергей

On Thu, Feb 25, 2016 at 3:32 PM, Kosyrev Serge <_deepfire@feelingofgreen.ru> wrote:
Thomas Tuegel
writes: Because it is not Applicative? Yes. For the same reason as Set, though, I do not think it should be Foldable or Traversable. It is convenient, but unsound. Or at least, less-sound. To fold or traverse Set and Map, I think the sound thing to do is to use one of the provided functions to convert them to a type where ordering is reflected structurally.
What about adding unstructural fold/traversal under different names?
That way we could have the convenience when we truly don't care about the directionality property, and the benefits of pure folding at the same time.
That's a good idea, but I don't think it really changes anything. The chief problem with types that aren't structurally ordered is really that there are multiple valid orders. For example, if [a] is our canonical structurally-ordered type, there are at least two obvious ways to write f :: Ord a => Set a -> [a]. I don't think an unstructured version of Foldable has much benefit over simply converting the improper type to a proper one. Regards, Tom

Thomas Tuegel
On Thu, Feb 25, 2016 at 3:32 PM, Kosyrev Serge <_deepfire@feelingofgreen.ru> wrote:
What about adding unstructural fold/traversal under different names?
That way we could have the convenience when we truly don't care about the directionality property, and the benefits of pure folding at the same time.
That's a good idea, but I don't think it really changes anything. The chief problem with types that aren't structurally ordered is really that there are multiple valid orders. For example, if [a] is our canonical structurally-ordered type, there are at least two obvious ways to write f :: Ord a => Set a -> [a]. I don't think an unstructured version of Foldable has much benefit over simply converting the improper type to a proper one.
Just off the top of my head -- efficiency? Or is that overhead imaginary? -- с уважениeм / respectfully, Косырев Сергей

On Fri, Feb 26, 2016 at 12:26 AM, Kosyrev Serge <_deepfire@feelingofgreen.ru> wrote:
Thomas Tuegel
writes: On Thu, Feb 25, 2016 at 3:32 PM, Kosyrev Serge <_deepfire@feelingofgreen.ru> wrote:
What about adding unstructural fold/traversal under different names?
That way we could have the convenience when we truly don't care about the directionality property, and the benefits of pure folding at the same time.
That's a good idea, but I don't think it really changes anything. The chief problem with types that aren't structurally ordered is really that there are multiple valid orders. For example, if [a] is our canonical structurally-ordered type, there are at least two obvious ways to write f :: Ord a => Set a -> [a]. I don't think an unstructured version of Foldable has much benefit over simply converting the improper type to a proper one.
Just off the top of my head -- efficiency? Or is that overhead imaginary?
I don't think there's a significant efficiency concern here. The list example should be subject to fusion, i.e. the intermediate list would never actually be constructed. Even if we were concerned about the fusion rules failing to fire, we could always define a simple iterator type which is perfectly well ordered with practically no overhead.

On Thu, Feb 25, 2016 at 4:47 AM, Thomas Tuegel
Foldable implies a notion of structural direction through the associativity of its members. Set is different from the well-behaved Foldables because its notion of direction or order is not structural, i.e. not preserved by operations on Set.
This is the first argument that I've seen in this whole messy thread that actually rings true for me - the fact that foldability is intricately tied to the ordering of elements is a very important one given that all that Monoid gives us is associativity and therefore any operation that we apply across a data structure that is *not* strictly ordered can have unpredictable results. Thank you very much for pointing this out. Converting from a Map or a Set to an ordered data structure before folding is obviously the principled thing to do - with Map in particular, the fact that the ordering of the keys is completely unrelated to the ordering of the values means that any non-commutative operation being applied across those values with foldMap is essentially a roll of the dice. This is troubling and something that should be corrected. This brings me to a question that I've often had but never asked, which is, where are all the typeclasses for operations which demand commutativity? In particular, CommutativeApplicative is a typeclass that I've longed for; a peer to Monad that represents parallelizable rather than sequential effectful operations. Kris

On Thu, Feb 25, 2016 at 09:29:48PM -0700, Kris Nuttycombe wrote:
On Thu, Feb 25, 2016 at 4:47 AM, Thomas Tuegel wrote:
Foldable implies a notion of structural direction through the associativity of its members. Set is different from the well-behaved Foldables because its notion of direction or order is not structural, i.e. not preserved by operations on Set.
This is the first argument that I've seen in this whole messy thread that actually rings true for me - the fact that foldability is intricately tied to the ordering of elements is a very important one given that all that Monoid gives us is associativity and therefore any operation that we apply across a data structure that is *not* strictly ordered can have unpredictable results. Thank you very much for pointing this out.
Converting from a Map or a Set to an ordered data structure before folding is obviously the principled thing to do - with Map in particular, the fact that the ordering of the keys is completely unrelated to the ordering of the values means that any non-commutative operation being applied across those values with foldMap is essentially a roll of the dice. This is troubling and something that should be corrected.
Without judgment, it appears that the answer for why things are not principled in this way is because 'it doesn't work for [our favorite datatypes]'. https://www.reddit.com/r/haskell/comments/47i5cp/safe_a_foldable_proposal/d0... Q. Shouldn't Foldable require a mappend that commutes? A. It can't, because that wouldn't work for Map k, Set, ... Q. Shouldn't there at least be an Ord somewhere? A. It can't, because "the Foldable/Monoid machinery for Maybe don't involve Ord in any way". So rather than being told "it should" or "it should not", I was told "it cannot". However, it appears that Map and Set *are* already 'converted' to an ordered structure. This puts us in the position of having instances for structures that logically shouldn't have them, but which work fine anyway. Their underlying, ordered implementation is apparently (ab)used to implement non-evil Foldable instances. Check out the QuickCheck below. This leads me to believe that Foldable works for unordered containers because people need it to work for unordered containers, and damn the principles, and (psst unordered containers aren't actually unordered anyway). Again, I state all this without judgment, and I don't think I've said anything new to the people who made these decisions (assuming I haven't gotten details wrong). --------- -- A quick test I wrote import Test.QuickCheck import Data.Foldable import qualified Data.HashSet as HS import qualified Data.Set as S prop_orderedHS xs = do xs' <- shuffle xs return $ fold (HS.fromList xs) == fold (HS.fromList xs') where types = (xs :: [String]) prop_orderedS xs = do xs' <- shuffle xs return $ fold (S.fromList xs) == fold (S.fromList xs') where types = (xs :: [String]) ------------ -- The basis for HashSet's and HashMap's implementation of `fold`, -- which uses the underlying arrays, which in turn are -- `GHC.Exts.Array#`s. -- Data/HashMap/Base.hs:907 foldrWithKey :: (k -> v -> a -> a) -> a -> HashMap k v -> a foldrWithKey f = go where go z Empty = z go z (Leaf _ (L k v)) = f k v z go z (BitmapIndexed _ ary) = A.foldr (flip go) z ary go z (Full ary) = A.foldr (flip go) z ary go z (Collision _ ary) = A.foldr (\ (L k v) z' -> f k v z') z ary
participants (5)
-
Bryan Richter
-
Gershom B
-
Kosyrev Serge
-
Kris Nuttycombe
-
Thomas Tuegel