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

Andreas Abel andreas.abel at ifi.lmu.de
Mon Oct 15 19:56:09 CEST 2012


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 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/



More information about the Libraries mailing list