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

Gábor Lehel illissius at gmail.com
Sun Oct 14 21:00:18 CEST 2012


On Sun, Oct 14, 2012 at 8:47 PM, Dan Burton <danburton.email at gmail.com> 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.

>
>
>
> On Sun, Oct 14, 2012 at 12:33 PM, Andreas Abel <andreas.abel at ifi.lmu.de>
> 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 <illissius at gmail.com> 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 at haskell.org
>>>> http://www.haskell.org/mailman/listinfo/libraries
>>>>
>>>
>>> _______________________________________________
>>> Libraries mailing list
>>> Libraries at 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 at ifi.lmu.de
>> http://www2.tcs.ifi.lmu.de/~abel/
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries
>
>
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>



-- 
Your ship was destroyed in a monadic eruption.



More information about the Libraries mailing list