[commit: ghc] master: Elaborate further on ZipList Applicative docs (ae0ccf8)

git at git.haskell.org git at git.haskell.org
Mon Mar 13 18:34:54 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/ae0ccf8c16f5ed394ab01a1863abd98a7a44ab60/ghc

>---------------------------------------------------------------

commit ae0ccf8c16f5ed394ab01a1863abd98a7a44ab60
Author: Chris Martin <ch.martin at gmail.com>
Date:   Sun Mar 12 15:15:29 2017 -0400

    Elaborate further on ZipList Applicative docs
    
    I was initially confused when I read "zipWithn" in the haddock for
    ZipList, went looking for a function named "zipWithn", and found that
    it didn't exist. This expands the docs to clarify that we're referring
    to the family of functions [zipWith, zipWith3, zipWith4, ...],
    capitalizes the letter "n" in "zipWithN" in attempt to make that more
    readable, and gives an example.
    
    I also moved this documentation from ZipList itself to the Applicative
    instance, so that it will show up in both the Ziplist documentation and
    in the list of Applicative instances.
    
    Reviewers: austin, hvr, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3324


>---------------------------------------------------------------

ae0ccf8c16f5ed394ab01a1863abd98a7a44ab60
 libraries/base/Control/Applicative.hs | 18 +++++++++++++-----
 1 file changed, 13 insertions(+), 5 deletions(-)

diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs
index 406f086..9045bcd 100644
--- a/libraries/base/Control/Applicative.hs
+++ b/libraries/base/Control/Applicative.hs
@@ -99,16 +99,24 @@ instance (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) where
     empty = WrapArrow zeroArrow
     WrapArrow u <|> WrapArrow v = WrapArrow (u <+> v)
 
--- | Lists, but with an 'Applicative' functor based on zipping, so that
---
--- @f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsn = 'ZipList' (zipWithn f xs1 ... xsn)@
---
+-- | Lists, but with an 'Applicative' functor based on zipping.
 newtype ZipList a = ZipList { getZipList :: [a] }
                   deriving ( Show, Eq, Ord, Read, Functor
                            , Foldable, Generic, Generic1)
 -- See Data.Traversable for Traversable instance due to import loops
 
--- | @since 2.01
+-- |
+-- > f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN
+--       = 'ZipList' (zipWithN f xs1 ... xsN)
+--
+-- where @zipWithN@ refers to the @zipWith@ function of the appropriate arity
+-- (@zipWith@, @zipWith3@, @zipWith4@, ...). For example:
+--
+-- > (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..]
+-- >     = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..])
+-- >     = ZipList {getZipList = ["a5","b6b6","c7c7c7"]}
+--
+-- @since 2.01
 instance Applicative ZipList where
     pure x = ZipList (repeat x)
     liftA2 f (ZipList xs) (ZipList ys) = ZipList (zipWith f xs ys)



More information about the ghc-commits mailing list