Proposal: alpha-rename the type signatures of foldl, foldl', and scanl to be consistent with foldr and scanr

Currently we have: foldl :: (a -> b -> a) -> a -> [b] -> a foldr :: (a -> b -> b) -> b -> [a] -> b I find this confusing. My brain doesn't do automatic alpha-renaming, so I end up thinking that these types are very different because they look very different. In fact, they are almost the same. Embarrassingly, it took me longer than it took to understand monads, GADTs, PolyKinds, and several other things before I realized it! So I propose that we use 'a' consistently to denote the type of the list elements, and 'b' to denote the type of the result: foldl :: (b -> a -> b) -> b -> [a] -> b foldr :: (a -> b -> b) -> b -> [a] -> b making it obvious that the only difference is the order of parameters to the accumulator. The total change would be to replace Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a with Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b I've attached a patch. Discussion period: 2 weeks Previously discussed at: http://www.reddit.com/r/haskell/comments/10q2ls/ -- Your ship was destroyed in a monadic eruption.

Seconded. This has been on my list of small time annoyances for years.
On Sun, Oct 14, 2012 at 10:28 AM, Gábor Lehel
Currently we have:
foldl :: (a -> b -> a) -> a -> [b] -> a
foldr :: (a -> b -> b) -> b -> [a] -> b
I find this confusing. My brain doesn't do automatic alpha-renaming, so I end up thinking that these types are very different because they look very different. In fact, they are almost the same. Embarrassingly, it took me longer than it took to understand monads, GADTs, PolyKinds, and several other things before I realized it!
So I propose that we use 'a' consistently to denote the type of the list elements, and 'b' to denote the type of the result:
foldl :: (b -> a -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
making it obvious that the only difference is the order of parameters to the accumulator.
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
I've attached a patch.
Discussion period: 2 weeks
Previously discussed at: http://www.reddit.com/r/haskell/comments/10q2ls/
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+1
There are a few other functions in Data.List that could benefit from
the same treatment:
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
mapAccumL :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y])
mapAccumR :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
genericLength :: Num i => [b] -> i
genericLength :: Num i => [a] -> i
genericSplitAt :: Integral i => i -> [b] -> ([b], [b])
genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
genericIndex :: Integral a => [b] -> a -> b
genericIndex :: Integral i => [a] -> i -> a
I'm not sure if we should change mapAccumL/R since 'a' and 'acc' are
maybe too similar.
Bas
On 14 October 2012 16:28, Gábor Lehel
Currently we have:
foldl :: (a -> b -> a) -> a -> [b] -> a
foldr :: (a -> b -> b) -> b -> [a] -> b
I find this confusing. My brain doesn't do automatic alpha-renaming, so I end up thinking that these types are very different because they look very different. In fact, they are almost the same. Embarrassingly, it took me longer than it took to understand monads, GADTs, PolyKinds, and several other things before I realized it!
So I propose that we use 'a' consistently to denote the type of the list elements, and 'b' to denote the type of the result:
foldl :: (b -> a -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
making it obvious that the only difference is the order of parameters to the accumulator.
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
I've attached a patch.
Discussion period: 2 weeks
Previously discussed at: http://www.reddit.com/r/haskell/comments/10q2ls/
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+1 to all. On 14.10.12 6:53 PM, Bas van Dijk wrote:
+1
There are a few other functions in Data.List that could benefit from the same treatment:
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumL :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumR :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
genericLength :: Num i => [b] -> i genericLength :: Num i => [a] -> i
genericSplitAt :: Integral i => i -> [b] -> ([b], [b]) genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
genericIndex :: Integral a => [b] -> a -> b genericIndex :: Integral i => [a] -> i -> a
I'm not sure if we should change mapAccumL/R since 'a' and 'acc' are maybe too similar.
Bas
On 14 October 2012 16:28, Gábor Lehel
wrote: Currently we have:
foldl :: (a -> b -> a) -> a -> [b] -> a
foldr :: (a -> b -> b) -> b -> [a] -> b
I find this confusing. My brain doesn't do automatic alpha-renaming, so I end up thinking that these types are very different because they look very different. In fact, they are almost the same. Embarrassingly, it took me longer than it took to understand monads, GADTs, PolyKinds, and several other things before I realized it!
So I propose that we use 'a' consistently to denote the type of the list elements, and 'b' to denote the type of the result:
foldl :: (b -> a -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
making it obvious that the only difference is the order of parameters to the accumulator.
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
I've attached a patch.
Discussion period: 2 weeks
Previously discussed at: http://www.reddit.com/r/haskell/comments/10q2ls/
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

At the risk of useless bikeshedding... might I suggest "r" as a
mnemonic for "result"?
foldl :: (a -> r -> r) -> r -> [a] -> r
foldr :: (r -> a -> r) -> r -> [a] -> r
-- Dan Burton
On Sun, Oct 14, 2012 at 12:33 PM, Andreas Abel
+1 to all.
On 14.10.12 6:53 PM, Bas van Dijk wrote:
+1
There are a few other functions in Data.List that could benefit from the same treatment:
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumL :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumR :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
genericLength :: Num i => [b] -> i genericLength :: Num i => [a] -> i
genericSplitAt :: Integral i => i -> [b] -> ([b], [b]) genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
genericIndex :: Integral a => [b] -> a -> b genericIndex :: Integral i => [a] -> i -> a
I'm not sure if we should change mapAccumL/R since 'a' and 'acc' are maybe too similar.
Bas
On 14 October 2012 16:28, Gábor Lehel
wrote: Currently we have:
foldl :: (a -> b -> a) -> a -> [b] -> a
foldr :: (a -> b -> b) -> b -> [a] -> b
I find this confusing. My brain doesn't do automatic alpha-renaming, so I end up thinking that these types are very different because they look very different. In fact, they are almost the same. Embarrassingly, it took me longer than it took to understand monads, GADTs, PolyKinds, and several other things before I realized it!
So I propose that we use 'a' consistently to denote the type of the list elements, and 'b' to denote the type of the result:
foldl :: (b -> a -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
making it obvious that the only difference is the order of parameters to the accumulator.
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
I've attached a patch.
Discussion period: 2 weeks
Previously discussed at: http://www.reddit.com/r/** haskell/comments/10q2ls/http://www.reddit.com/r/haskell/comments/10q2ls/
-- Your ship was destroyed in a monadic eruption.
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch.
Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY
andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~**abel/ http://www2.tcs.ifi.lmu.de/~abel/
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries

+1 to this "r" version.
Roman
* Dan Burton
At the risk of useless bikeshedding... might I suggest "r" as a mnemonic for "result"?
foldl :: (a -> r -> r) -> r -> [a] -> r foldr :: (r -> a -> r) -> r -> [a] -> r
-- Dan Burton
On Sun, Oct 14, 2012 at 12:33 PM, Andreas Abel
wrote: +1 to all.
On 14.10.12 6:53 PM, Bas van Dijk wrote:
+1
There are a few other functions in Data.List that could benefit from the same treatment:
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumL :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumR :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
genericLength :: Num i => [b] -> i genericLength :: Num i => [a] -> i
genericSplitAt :: Integral i => i -> [b] -> ([b], [b]) genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
genericIndex :: Integral a => [b] -> a -> b genericIndex :: Integral i => [a] -> i -> a
I'm not sure if we should change mapAccumL/R since 'a' and 'acc' are maybe too similar.
Bas
On 14 October 2012 16:28, Gábor Lehel
wrote: Currently we have:
foldl :: (a -> b -> a) -> a -> [b] -> a
foldr :: (a -> b -> b) -> b -> [a] -> b
I find this confusing. My brain doesn't do automatic alpha-renaming, so I end up thinking that these types are very different because they look very different. In fact, they are almost the same. Embarrassingly, it took me longer than it took to understand monads, GADTs, PolyKinds, and several other things before I realized it!
So I propose that we use 'a' consistently to denote the type of the list elements, and 'b' to denote the type of the result:
foldl :: (b -> a -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
making it obvious that the only difference is the order of parameters to the accumulator.
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
I've attached a patch.
Discussion period: 2 weeks
Previously discussed at: http://www.reddit.com/r/** haskell/comments/10q2ls/http://www.reddit.com/r/haskell/comments/10q2ls/
-- Your ship was destroyed in a monadic eruption.
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch.
Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY
andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~**abel/ http://www2.tcs.ifi.lmu.de/~abel/
______________________________**_________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/**mailman/listinfo/librarieshttp://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

On Sun, Oct 14, 2012 at 8:47 PM, Dan Burton
At the risk of useless bikeshedding... might I suggest "r" as a mnemonic for "result"?
foldl :: (a -> r -> r) -> r -> [a] -> r foldr :: (r -> a -> r) -> r -> [a] -> r
-- Dan Burton
'r' is the version I originally used myself (see reddit). But then you have to change the foldrs too, and quite possibly a lot of other functions, and get dragged into a big discussion over when is 'r' a better mnemonic than 'b' and when is it not. Simply swapping 'a' and 'b' in the left folds captures most of the benefit for least cost. Same goes for most of the other suggestions I have seen (I don't find the existing signatures actively confusing, merely suboptimal), but if sentiment is overwhelmingly in favor of making further changes I can be swayed. For now I wanted to propose a minimal change with the best chance of attracting a broad consensus.
On Sun, Oct 14, 2012 at 12:33 PM, Andreas Abel
wrote: +1 to all.
On 14.10.12 6:53 PM, Bas van Dijk wrote:
+1
There are a few other functions in Data.List that could benefit from the same treatment:
mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumL :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumR :: (acc -> a -> (acc, b)) -> acc -> [a] -> (acc, [b])
genericLength :: Num i => [b] -> i genericLength :: Num i => [a] -> i
genericSplitAt :: Integral i => i -> [b] -> ([b], [b]) genericSplitAt :: Integral i => i -> [a] -> ([a], [a])
genericIndex :: Integral a => [b] -> a -> b genericIndex :: Integral i => [a] -> i -> a
I'm not sure if we should change mapAccumL/R since 'a' and 'acc' are maybe too similar.
Bas
On 14 October 2012 16:28, Gábor Lehel
wrote: Currently we have:
foldl :: (a -> b -> a) -> a -> [b] -> a
foldr :: (a -> b -> b) -> b -> [a] -> b
I find this confusing. My brain doesn't do automatic alpha-renaming, so I end up thinking that these types are very different because they look very different. In fact, they are almost the same. Embarrassingly, it took me longer than it took to understand monads, GADTs, PolyKinds, and several other things before I realized it!
So I propose that we use 'a' consistently to denote the type of the list elements, and 'b' to denote the type of the result:
foldl :: (b -> a -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
making it obvious that the only difference is the order of parameters to the accumulator.
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
I've attached a patch.
Discussion period: 2 weeks
Previously discussed at: http://www.reddit.com/r/haskell/comments/10q2ls/
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch.
Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY
andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Your ship was destroyed in a monadic eruption.

On Sun, Oct 14, 2012 at 12:00 PM, Gábor Lehel
On Sun, Oct 14, 2012 at 8:47 PM, Dan Burton
wrote: At the risk of useless bikeshedding... might I suggest "r" as a mnemonic for "result"?
foldl :: (a -> r -> r) -> r -> [a] -> r foldr :: (r -> a -> r) -> r -> [a] -> r
-- Dan Burton
'r' is the version I originally used myself (see reddit). But then you have to change the foldrs too, and quite possibly a lot of other functions, and get dragged into a big discussion over when is 'r' a better mnemonic than 'b' and when is it not.
Simply swapping 'a' and 'b' in the left folds captures most of the benefit for least cost.
Same goes for most of the other suggestions I have seen (I don't find the existing signatures actively confusing, merely suboptimal), but if sentiment is overwhelmingly in favor of making further changes I can be swayed. For now I wanted to propose a minimal change with the best chance of attracting a broad consensus.
+1

On Sun, Oct 14, 2012 at 09:00:18PM +0200, Gábor Lehel wrote:
On Sun, Oct 14, 2012 at 8:47 PM, Dan Burton
wrote: At the risk of useless bikeshedding... might I suggest "r" as a mnemonic for "result"?
foldl :: (a -> r -> r) -> r -> [a] -> r foldr :: (r -> a -> r) -> r -> [a] -> r
-- Dan Burton
'r' is the version I originally used myself (see reddit). But then you have to change the foldrs too, and quite possibly a lot of other functions, and get dragged into a big discussion over when is 'r' a better mnemonic than 'b' and when is it not.
Simply swapping 'a' and 'b' in the left folds captures most of the benefit for least cost.
Same goes for most of the other suggestions I have seen (I don't find the existing signatures actively confusing, merely suboptimal), but if sentiment is overwhelmingly in favor of making further changes I can be swayed. For now I wanted to propose a minimal change with the best chance of attracting a broad consensus.
I'm in favor of the simple change, so +1 ;) Cheers, Simon

On 15 October 2012 03:28, Simon Hengel
On Sun, Oct 14, 2012 at 09:00:18PM +0200, Gábor Lehel wrote:
On Sun, Oct 14, 2012 at 8:47 PM, Dan Burton
wrote: At the risk of useless bikeshedding... might I suggest "r" as a mnemonic for "result"?
foldl :: (a -> r -> r) -> r -> [a] -> r foldr :: (r -> a -> r) -> r -> [a] -> r
-- Dan Burton
'r' is the version I originally used myself (see reddit). But then you have to change the foldrs too, and quite possibly a lot of other functions, and get dragged into a big discussion over when is 'r' a better mnemonic than 'b' and when is it not.
Simply swapping 'a' and 'b' in the left folds captures most of the benefit for least cost.
Same goes for most of the other suggestions I have seen (I don't find the existing signatures actively confusing, merely suboptimal), but if sentiment is overwhelmingly in favor of making further changes I can be swayed. For now I wanted to propose a minimal change with the best chance of attracting a broad consensus.
I'm in favor of the simple change, so +1 ;)
+1 Conrad.

+1
On Sun, Oct 14, 2012 at 7:58 PM, Conrad Parker
On 15 October 2012 03:28, Simon Hengel
wrote: On Sun, Oct 14, 2012 at 09:00:18PM +0200, Gábor Lehel wrote:
On Sun, Oct 14, 2012 at 8:47 PM, Dan Burton
wrote: At the risk of useless bikeshedding... might I suggest "r" as a mnemonic for "result"?
foldl :: (a -> r -> r) -> r -> [a] -> r foldr :: (r -> a -> r) -> r -> [a] -> r
-- Dan Burton
'r' is the version I originally used myself (see reddit). But then you have to change the foldrs too, and quite possibly a lot of other functions, and get dragged into a big discussion over when is 'r' a better mnemonic than 'b' and when is it not.
Simply swapping 'a' and 'b' in the left folds captures most of the benefit for least cost.
Same goes for most of the other suggestions I have seen (I don't find the existing signatures actively confusing, merely suboptimal), but if sentiment is overwhelmingly in favor of making further changes I can be swayed. For now I wanted to propose a minimal change with the best chance of attracting a broad consensus.
I'm in favor of the simple change, so +1 ;)
+1
Conrad.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

'r' is the version I originally used myself (see reddit). But then you have to change the foldrs too, and quite possibly a lot of other functions
This is true, but these are merely alpha-renaming changes, so the only negative consequence is bikeshedding. I suggest we restrict the scope of this discussion to changing (at most) only list functions in the base package. and get dragged into a big discussion over when is 'r' a
better mnemonic than 'b' and when is it not.
Indeed. However, I don't think there's really much that can be said in this discussion, so let's go ahead and get it over with. a and b are sufficiently early in the
alphabet to be generic; “r” might look confusingly special to new users.
There's this. I see the idea here, but I don't think newcomers will actually have this problem. *handwave* One other concern might be that it conflicts with other conventions. The one that comes to mind is the Reader monad, where "r" is used in the documentation as the type of the reading environment. (I personally would prefer Reader to use "e" as a mnemonic for "environment", but that's a whole different discussion.) Again, I don't think that these differing uses of "r" will actually cause much strife. *handwave* -- Dan Burton

On Mon, Oct 15, 2012 at 9:23 AM, Dan Burton
'r' is the version I originally used myself (see reddit). But then you have to change the foldrs too, and quite possibly a lot of other functions
This is true, but these are merely alpha-renaming changes, so the only negative consequence is bikeshedding. I suggest we restrict the scope of this discussion to changing (at most) only list functions in the base package.
Just to throw some salt in the fire and open another can of beeswax, I usually use 'accum' for this things.

On Mon, Oct 15, 2012 at 6:39 PM, Evan Laforge
This is true, but these are merely alpha-renaming changes, so the only negative consequence is bikeshedding. I suggest we restrict the scope of this discussion to changing (at most) only list functions in the base package.
Just to throw some salt in the fire and open another can of beeswax, I usually use 'accum' for this things.
A fire? Where? Is that safe with all the emails lying about? -- Your ship was destroyed in a monadic eruption.

I'd be against a version of this proposal that actually switched to
multi-character names.
On Mon, Oct 15, 2012 at 12:50 PM, Gábor Lehel
On Mon, Oct 15, 2012 at 6:39 PM, Evan Laforge
wrote: This is true, but these are merely alpha-renaming changes, so the only negative consequence is bikeshedding. I suggest we restrict the scope of this discussion to changing (at most) only list functions in the base package.
Just to throw some salt in the fire and open another can of beeswax, I usually use 'accum' for this things.
A fire? Where? Is that safe with all the emails lying about?
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

I like to add that if you define a class for structures and according element types that support both foldl and foldr, and you are not using the RMonad trick, then the name of the types really matter: class Foldable v a b where foldl :: (a -> b -> a) -> a -> v b -> a foldr :: (a -> b -> b) -> b -> v a -> b The accumulator type would not need to be storable in the structure 'v' but if the Fold class uses the variable names from the Prelude then both accumulator and element type are constrained. I think the accumulator should not be named 'r' because there are many result types in the List module that are not named 'r' and should not be, for instance because argument and result have the same type or are just Int or Bool. The distinguishing feature of a result type is that it is the last type in a chain of arrows, but you can hardly express this using the variable name.

I think the accumulator should not be named 'r' because there are many result types in the List module that are not named 'r' and should not be, for instance because argument and result have the same type or are just Int or Bool.
I agree that many result types in the List module should not be named 'r'. I therefore suggest that the convention be used only in cases like "foldr" where there are *two or more type variables*, and we can benefit from more clearly distinguishing one from the others. The current convention seems to be left-to-right a-thru-z, which as the foldr vs foldl issue illustrates, is suboptimal. The distinguishing feature of a result type is that it is the last type in
a chain of arrows, but you can hardly express this using the variable name.
Ah, but this is precisely why I personally do use the "r" convention: because anywhere in the type signature where I see an "r", I know that it must match with the "result" type (the one at the end of the chain of arrows). I believe I picked up the "r" convention from Control.Monad.Cont, or possibly from Data.Conduit. This is what "r" means to me, and I think it is a convention worth pushing onto everyone else. ;) After looking over the type signatures of Data.List, I propose the following "rule of thumb": When the final result type (the one at the end of a chain of arrows) of a function is a single polymorphic type with no additional structure (e.g. just "a" not "[a]" or "Maybe a"), and the type signature of the function involves more than one type variable, then the type variable appearing in the final position should be "r". (If there is just one type variable, then it should be "a") According to this rule of thumb, only the following changes would be made: foldl :: (r -> a -> r) -> r -> [a] -> r foldl' :: (r -> a -> r) -> r -> [a] -> r foldr :: (a -> r -> r) -> r -> [a] -> r Technically this means that the "genericBlah" functions should also change, but those have a special case of their own, which is that the integral should be "i". Oddly, this convention is not followed consistently, so while we're alpha-renaming, might I also suggest that we make the genericBlah docs consistent by using "i" for the integral, and "a" for the list member. (e.g. "genericIndex :: Integral i => [a] -> i -> a") Another potential reason to dislike this proposal is that GHCi will not follow this convention, and thus will not suggest the same type signature. (Although it could be made to, since I believe I have specified a precise algorithm.) -- Dan Burton

On Mon, 15 Oct 2012, Dan Burton wrote:
Ah, but this is precisely why I personally do use the "r" convention: because anywhere in the type signature where I see an "r", I know that it must match with the "result" type (the one at the end of the chain of arrows).
Would you also call input types 'i', or maybe 'a' because they are arguments, or 'p' because they are parameters?

Since you insist... -1 to use of 'r' in result [If at all, the letter 'z' would be more logical (works for functions with more parameters).] Unrelated: -1 to long type variable names like 'accum' Cheers, Andreas On 15.10.2012 19:46, Dan Burton wrote:
I think the accumulator should not be named 'r' because there are many result types in the List module that are not named 'r' and should not be, for instance because argument and result have the same type or are just Int or Bool.
I agree that many result types in the List module should not be named 'r'. I therefore suggest that the convention be used only in cases like "foldr" where there are *two or more type variables*, and we can benefit from more clearly distinguishing one from the others. The current convention seems to be left-to-right a-thru-z, which as the foldr vs foldl issue illustrates, is suboptimal.
The distinguishing feature of a result type is that it is the last type in a chain of arrows, but you can hardly express this using the variable name.
Ah, but this is precisely why I personally do use the "r" convention: because anywhere in the type signature where I see an "r", I know that it must match with the "result" type (the one at the end of the chain of arrows). I believe I picked up the "r" convention from Control.Monad.Cont, or possibly from Data.Conduit. This is what "r" means to me, and I think it is a convention worth pushing onto everyone else. ;)
After looking over the type signatures of Data.List, I propose the following "rule of thumb":
When the final result type (the one at the end of a chain of arrows) of a function is a single polymorphic type with no additional structure (e.g. just "a" not "[a]" or "Maybe a"), and the type signature of the function involves more than one type variable, then the type variable appearing in the final position should be "r". (If there is just one type variable, then it should be "a")
According to this rule of thumb, only the following changes would be made:
foldl :: (r -> a -> r) -> r -> [a] -> r foldl' :: (r -> a -> r) -> r -> [a] -> r foldr :: (a -> r -> r) -> r -> [a] -> r
Technically this means that the "genericBlah" functions should also change, but those have a special case of their own, which is that the integral should be "i". Oddly, this convention is not followed consistently, so while we're alpha-renaming, might I also suggest that we make the genericBlah docs consistent by using "i" for the integral, and "a" for the list member. (e.g. "genericIndex :: Integral i => [a] -> i -> a")
Another potential reason to dislike this proposal is that GHCi will not follow this convention, and thus will not suggest the same type signature. (Although it could be made to, since I believe I have specified a precise algorithm.)
-- Dan Burton
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

On 10/15/12 1:56 PM, Andreas Abel wrote:
Since you insist...
-1 to use of 'r' in result [If at all, the letter 'z' would be more logical (works for functions with more parameters).]
Unrelated:
-1 to long type variable names like 'accum'
+1, er -1, er what Andreas said. (+1 for the original simple swapping of a and b, btw) -- Live well, ~wren

Do note that my proposed "r" solution does not solve the problem of scanl vs scanr. (!!!) Another reason to dislike it. Would you also call input types 'i', or maybe 'a' because they are
arguments, or 'p' because they are parameters?
I wouldn't. The allure of using "r" is that when you see "r" *earlier* in the type signature, then you know it must be the same as the "result". Using a mnemonic for function inputs doesn't carry the same benefit, although for something like Conduit "i"nput and "o"utput make sense. If at all, the letter 'z' would be more logical I'd be happy with "z" just as much as "r". "z" is nice because it obviously doesn't stand for anything, but it still holds mnemonic value for the concept of "the end". Let the "z versus r" bikeshedding wars begin! [z] works for functions with more parameters Is that really a concern? It takes 18 distinct parameters to get from a to r. -1 for using anything longer than "acc". I'd be ok with just "acc" as is used currently in docs for mapAccum*, though I'd prefer a single-letter variable. -- Dan Burton

On October 15, 2012 13:46:53 Dan Burton wrote:
After looking over the type signatures of Data.List, I propose the following "rule of thumb":
When the final result type (the one at the end of a chain of arrows) of a function is a single polymorphic type with no additional structure (e.g. just "a" not "[a]" or "Maybe a"), and the type signature of the function involves more than one type variable, then the type variable appearing in the final position should be "r". (If there is just one type variable, then it should be "a")
...
Another potential reason to dislike this proposal is that GHCi will not follow this convention, and thus will not suggest the same type signature. (Although it could be made to, since I believe I have specified a precise algorithm.)
Talking about algorithms, I was working on a draft paper awhile back assigning measures to types based on their shapes (if you do read it, please note that 2.1 feels right to me, 2.2 is okay, and 2.3 needs more thought). http://www.sharcnet.ca/~tyson/haskell/papers/TypeShape.pdf One of the things coming out of this, I believe, was a fairly strong argument that the key feature of a type (without a higher understanding) is the number of occurances its elementary components make. To this end, I would suggest the following algorithmic approach (I don't actually have an particular reason for the sub-sort in (3) other than some choice has to be made) 1 - count the number of occurances of each free variable, 2 - sort them from most frequently occuring to least, 3 - sub-sort ones of the same frequency according to order of appearance, and 4 - assign the names a, b, c, ... according to the sorted order. For example, under this algorithm, the canonical form of these signatures Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: Foldable t => (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: Foldable t => (a -> b -> a) -> a -> t b -> a mapAccumL :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) mapAccumR :: (acc -> x -> (acc, y)) -> acc -> [x] -> (acc, [y]) genericLength :: Num i => [b] -> i genericSplitAt :: Integral i => i -> [b] -> ([b], [b]) genericIndex :: Integral a => [b] -> a -> b would be (note that I'm counting constraints occurances too) Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: Foldable b => (a -> c -> a) -> a -> b c -> a Data.Foldable.foldl' :: Foldable b => (a -> c -> a) -> a -> b c -> a mapAccumL :: (a -> b -> (a, c)) -> a -> [b] -> (a, [c]) mapAccumR :: (a -> b -> (a, c)) -> a -> [b] -> (a, [c]) genericLength :: Num a => [b] -> a genericSplitAt :: Integral b => b -> [a] -> ([a], [a]) genericIndex :: Integral a => [b] -> a -> b Not perfect for sure, but not too bad for a pretty dumb algorithm I think. Cheers! -Tyson PS: Actually (disclaimer that I haven't though alot about this yet), I expect that this is the best dumb algorithm possible ignoring possible sub-sort variants (i.e., humans would rank it's output as preferred most often over a large enough random set of actual types).

The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
+1 Cheers, Simon

+1 On 14.10.12 7:01 PM, Simon Hengel wrote:
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
+1
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

Hi, Am Sonntag, den 14.10.2012, 16:28 +0200 schrieb Gábor Lehel:
foldl :: (b -> a -> b) -> b -> [a] -> b foldr :: (a -> b -> b) -> b -> [a] -> b Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
+1. Also preferring this over “r”; a and b are sufficiently early in the alphabet to be generic; “r” might look confusingly special to new users. Greetings, Joachim -- Joachim "nomeata" Breitner mail@joachim-breitner.de | nomeata@debian.org | GPG: 0x4743206C xmpp: nomeata@joachim-breitner.de | http://www.joachim-breitner.de/

Amen! (+1).
I often have to rewrite the signature of foldl to the suggested version as
a sanity check. I thought it just was my personal mental deficiency.
I prefer "b" to "r".
-- Conall
On Sun, Oct 14, 2012 at 7:28 AM, Gábor Lehel
Currently we have:
foldl :: (a -> b -> a) -> a -> [b] -> a
foldr :: (a -> b -> b) -> b -> [a] -> b
I find this confusing. My brain doesn't do automatic alpha-renaming, so I end up thinking that these types are very different because they look very different. In fact, they are almost the same. Embarrassingly, it took me longer than it took to understand monads, GADTs, PolyKinds, and several other things before I realized it!
So I propose that we use 'a' consistently to denote the type of the list elements, and 'b' to denote the type of the result:
foldl :: (b -> a -> b) -> b -> [a] -> b
foldr :: (a -> b -> b) -> b -> [a] -> b
making it obvious that the only difference is the order of parameters to the accumulator.
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
I've attached a patch.
Discussion period: 2 weeks
Previously discussed at: http://www.reddit.com/r/haskell/comments/10q2ls/
-- Your ship was destroyed in a monadic eruption.
_______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc

On Sun, Oct 14, 2012 at 10:28 AM, Gábor Lehel
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
+1 on this version of the proposal. Anthony

On 14 October 2012 15:28, Gábor Lehel
The total change would be to replace
Prelude.foldl :: (a -> b -> a) -> a -> [b] -> a Prelude.scanl :: (a -> b -> a) -> a -> [b] -> [a] Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a Data.Foldable.foldl :: (a -> b -> a) -> a -> t b -> a Data.Foldable.foldl' :: (a -> b -> a) -> a -> t b -> a
with
Prelude.foldl :: (b -> a -> b) -> b -> [a] -> b Prelude.scanl :: (b -> a -> b) -> b -> [a] -> [b] Data.List.foldl' :: (b -> a -> b) -> b -> [a] -> b Data.Foldable.foldl :: (b -> a -> b) -> b -> t a -> b Data.Foldable.foldl' :: (b -> a -> b) -> b -> t a -> b
I've attached a patch.
+1 We do indeed have a bit of a culture of using too short names for type variables, but they are fine in this case. -- Push the envelope. Watch it bend.

On Sun, Oct 14, 2012 at 04:28:58PM +0200, Gábor Lehel wrote:
I've attached a patch.
I've applied the patch, and also the other agreed changes. Thanks Ian

Hi,
We should make this same change in Control.Monad:
foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a to:
foldM :: Monad m => (b -> a -> m b) -> b -> [a] -> m b
foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () to:
foldM_ :: Monad m => (b -> a -> m b) -> b -> [a] -> m ()
Bas
On 27 October 2012 22:07, Ian Lynagh
On Sun, Oct 14, 2012 at 04:28:58PM +0200, Gábor Lehel wrote:
I've attached a patch.
I've applied the patch, and also the other agreed changes.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

+1 On 09.11.12 10:29 AM, Bas van Dijk wrote:
Hi,
We should make this same change in Control.Monad:
foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a to: foldM :: Monad m => (b -> a -> m b) -> b -> [a] -> m b
foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () to: foldM_ :: Monad m => (b -> a -> m b) -> b -> [a] -> m ()
Bas
On 27 October 2012 22:07, Ian Lynagh
wrote: On Sun, Oct 14, 2012 at 04:28:58PM +0200, Gábor Lehel wrote:
I've attached a patch.
I've applied the patch, and also the other agreed changes.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Andreas Abel <>< Du bist der geliebte Mensch. Theoretical Computer Science, University of Munich Oettingenstr. 67, D-80538 Munich, GERMANY andreas.abel@ifi.lmu.de http://www2.tcs.ifi.lmu.de/~abel/

Ian,
I think you missed some fixes in Data.Foldable from the original patch:
foldl :: (a -> b -> a) -> a -> t b -> a to:
foldl :: (b -> a -> b) -> b -> t a -> b
foldl' :: (a -> b -> a) -> a -> t b -> a to:
foldl' :: (b -> a -> b) -> b -> t a -> b
foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m a to:
foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
On 9 November 2012 10:29, Bas van Dijk
Hi,
We should make this same change in Control.Monad:
foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a to: foldM :: Monad m => (b -> a -> m b) -> b -> [a] -> m b
foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () to: foldM_ :: Monad m => (b -> a -> m b) -> b -> [a] -> m ()
Bas
On 27 October 2012 22:07, Ian Lynagh
wrote: On Sun, Oct 14, 2012 at 04:28:58PM +0200, Gábor Lehel wrote:
I've attached a patch.
I've applied the patch, and also the other agreed changes.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Hmm, I think foldlM was something that I missed. But +1 to all.
On Fri, Nov 9, 2012 at 11:32 AM, Bas van Dijk
Ian,
I think you missed some fixes in Data.Foldable from the original patch:
foldl :: (a -> b -> a) -> a -> t b -> a to: foldl :: (b -> a -> b) -> b -> t a -> b
foldl' :: (a -> b -> a) -> a -> t b -> a to: foldl' :: (b -> a -> b) -> b -> t a -> b
foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m a to: foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
On 9 November 2012 10:29, Bas van Dijk
wrote: Hi,
We should make this same change in Control.Monad:
foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> m a to: foldM :: Monad m => (b -> a -> m b) -> b -> [a] -> m b
foldM_ :: Monad m => (a -> b -> m a) -> a -> [b] -> m () to: foldM_ :: Monad m => (b -> a -> m b) -> b -> [a] -> m ()
Bas
On 27 October 2012 22:07, Ian Lynagh
wrote: On Sun, Oct 14, 2012 at 04:28:58PM +0200, Gábor Lehel wrote:
I've attached a patch.
I've applied the patch, and also the other agreed changes.
Thanks Ian
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
-- Your ship was destroyed in a monadic eruption.

Hi Bas, On Fri, Nov 09, 2012 at 11:32:05AM +0100, Bas van Dijk wrote:
I think you missed some fixes in Data.Foldable from the original patch:
foldl :: (a -> b -> a) -> a -> t b -> a to: foldl :: (b -> a -> b) -> b -> t a -> b
foldl' :: (a -> b -> a) -> a -> t b -> a to: foldl' :: (b -> a -> b) -> b -> t a -> b
These are already done as far as I can see?
foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m a to: foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
I'll do this one. Thanks Ian

On 10 November 2012 15:19, Ian Lynagh
These are already done as far as I can see?
You're right. I was looking at the wrong patch.
foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m a to: foldlM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
I'll do this one.
Thanks, Bas
participants (19)
-
Andreas Abel
-
Anthony Cowley
-
Bas van Dijk
-
Conal Elliott
-
Conrad Parker
-
Dan Burton
-
Dan Doel
-
Edward Kmett
-
Evan Laforge
-
Gábor Lehel
-
Henning Thielemann
-
Ian Lynagh
-
Joachim Breitner
-
Johan Tibell
-
Roman Cheplyaka
-
Simon Hengel
-
Thomas Schilling
-
Tyson Whitehead
-
wren ng thornton