Data.Traversable documentation MR 5873

Carter Schonwald carter.schonwald at gmail.com
Wed Jun 2 16:02:33 UTC 2021


This list is always topical for such feedback and design proposals (in fact
generally all such base/boot lib changes should ideally be at least
proposed here for visibility over time )

On Tue, Jun 1, 2021 at 10:59 PM Viktor Dukhovni <ietf-dane at dukhovni.org>
wrote:

> I hope it is acceptable on this list to solicit feedback on a
> documentation MR for the base library, specifically the Data.Traversable
> module:
>
>     https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5873
>
> The rewrite touches a lot of text, and so most of you are likely to not
> find time for the full review that it perhaps deserves.  But I hope that
> one or two of you would be inclined to give it a go.
>
> In addition to the specifics of the exposition, both in Data.Traversable,
> and in Data.Foldable I'm opting for a somewhat new layout of the module
> documentation, with just a brief blurb at the top, then all the function
> synopses, and only after all that the detailed prose and laws, which
> were historically at the top of each module's documentation.
>
> I think the "prose last" format is more suitable for the typical user
> who wants to quickly glance at the documentation of a single function,
> or see what functions are in the module.  The detailed exposition is for
> those who want to take the time to be introduced to the relevant
> concepts.
>
> Section headings and links make it possible to navigate to the overview
> if one is instead interested in the introductory prose.
>
> I hope this format is a step in the right direction, or if not, this is
> a good opportunity to correct the document structure.
>
> Lastly, a comment in the MR asks whether it would be a good idea
> to tweak the definitions of mapAccumL and mapAccumR to "amp up"
> the use of coercions in the hope of a performance payoff.  See
> proposed patch below...
>
> --
>     Viktor.
>
> diff --git a/libraries/base/Data/Traversable.hs
> b/libraries/base/Data/Traversable.hs
> index db7e548325..6871e411a0 100644
> --- a/libraries/base/Data/Traversable.hs
> +++ b/libraries/base/Data/Traversable.hs
> @@ -432,8 +432,10 @@ forM = flip mapM
>  -- >>> mapAccumL (\a b -> (a <> show b, a)) "0" [1..5]
>  -- ("012345",["0","01","012","0123","01234"])
>  --
> -mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
> -mapAccumL f s t = runStateL (traverse (StateL . flip f) t) s
> +type TraverseL t s a b = (a -> StateL s b) -> t a -> StateL s (t b)
> +mapAccumL :: forall t s a b. Traversable t
> +          => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
> +mapAccumL f s t = coerce (traverse :: TraverseL t s a b) (flip f) t s
>
>  -- |The 'mapAccumR' function behaves like a combination of 'fmap'
>  -- and 'Data.Foldable.foldr'; it applies a function to each element of a
> structure,
> @@ -450,8 +452,10 @@ mapAccumL f s t = runStateL (traverse (StateL . flip
> f) t) s
>  -- >>> mapAccumR (\a b -> (a <> show b, a)) "0" [1..5]
>  -- ("054321",["05432","0543","054","05","0"])
>  --
> -mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
> -mapAccumR f s t = runStateR (traverse (StateR . flip f) t) s
> +type TraverseR t s a b = (a -> StateR s b) -> t a -> StateR s (t b)
> +mapAccumR :: forall t s a b. Traversable t
> +          => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
> +mapAccumR f s t = coerce (traverse :: TraverseR t s a b) (flip f) t s
>
>  -- | This function may be used as a value for `fmap` in a `Functor`
>  --   instance, provided that 'traverse' is defined. (Using
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20210602/86950985/attachment.html>


More information about the Libraries mailing list