[commit: ghc] master: Add some complexities to Data.List documentation (#15003) (ae4e4ba)

git at git.haskell.org git at git.haskell.org
Tue Dec 18 14:47:19 UTC 2018


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

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

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

commit ae4e4ba655f2d0d8a5cc8488ada628726e9cc147
Author: Sven Tennie <sven.tennie at gmail.com>
Date:   Sun Dec 16 17:25:24 2018 +0100

    Add some complexities to Data.List documentation (#15003)
    
    Namely for:
    - stripPrefix
    - isPrefixOf
    - intersperse
    - tails
    - map
    - scanl
    - scanl1
    - scanl'
    - scanr
    - scanr1
    - zip
    - zipWith
    
    Add examples to `zipWith` and `map`.


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

ae4e4ba655f2d0d8a5cc8488ada628726e9cc147
 libraries/base/Data/OldList.hs | 12 ++++++------
 libraries/base/GHC/Base.hs     |  5 ++++-
 libraries/base/GHC/List.hs     | 26 ++++++++++++++++----------
 3 files changed, 26 insertions(+), 17 deletions(-)

diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs
index 99ad914..559823c 100644
--- a/libraries/base/Data/OldList.hs
+++ b/libraries/base/Data/OldList.hs
@@ -241,9 +241,9 @@ infix 5 \\ -- comment to fool cpp: https://downloads.haskell.org/~ghc/latest/doc
 dropWhileEnd :: (a -> Bool) -> [a] -> [a]
 dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
 
--- | The 'stripPrefix' function drops the given prefix from a list.
--- It returns 'Nothing' if the list did not start with the prefix
--- given, or 'Just' the list after the prefix, if it does.
+-- | /O(min(m,n))/. The 'stripPrefix' function drops the given prefix from a
+-- list. It returns 'Nothing' if the list did not start with the prefix given,
+-- or 'Just' the list after the prefix, if it does.
 --
 -- >>> stripPrefix "foo" "foobar"
 -- Just "bar"
@@ -319,7 +319,7 @@ findIndices p ls = build $ \c n ->
   in foldr go (\_ -> n) ls 0#
 #endif  /* USE_REPORT_PRELUDE */
 
--- | The 'isPrefixOf' function takes two lists and returns 'True'
+-- | /O(min(m,n))/. The 'isPrefixOf' function takes two lists and returns 'True'
 -- iff the first list is a prefix of the second.
 --
 -- >>> "Hello" `isPrefixOf` "Hello World!"
@@ -509,7 +509,7 @@ intersectBy _  [] _     =  []
 intersectBy _  _  []    =  []
 intersectBy eq xs ys    =  [x | x <- xs, any (eq x) ys]
 
--- | The 'intersperse' function takes an element and a list and
+-- | /O(n)/. The 'intersperse' function takes an element and a list and
 -- \`intersperses\' that element between the elements of the list.
 -- For example,
 --
@@ -1001,7 +1001,7 @@ inits                   = map toListSB . scanl' snocSB emptySB
 -- if it fuses with a consumer, and it would generally lead to serious
 -- loss of sharing if allowed to fuse with a producer.
 
--- | The 'tails' function returns all final segments of the argument,
+-- | /O(n)/. The 'tails' function returns all final segments of the argument,
 -- longest first.  For example,
 --
 -- >>> tails "abc"
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 924a1ff..8b14d48 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -1095,11 +1095,14 @@ augment g xs = g (:) xs
 --              map
 ----------------------------------------------
 
--- | 'map' @f xs@ is the list obtained by applying @f@ to each element
+-- | /O(n)/. 'map' @f xs@ is the list obtained by applying @f@ to each element
 -- of @xs@, i.e.,
 --
 -- > map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn]
 -- > map f [x1, x2, ...] == [f x1, f x2, ...]
+--
+-- >>> map (+1) [1, 2, 3]
+--- [2,3,4]
 
 map :: (a -> b) -> [a] -> [b]
 {-# NOINLINE [0] map #-}
diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs
index fced329..df2c19a 100644
--- a/libraries/base/GHC/List.hs
+++ b/libraries/base/GHC/List.hs
@@ -262,7 +262,7 @@ product                 :: (Num a) => [a] -> a
 {-# INLINE product #-}
 product                 =  foldl (*) 1
 
--- | 'scanl' is similar to 'foldl', but returns a list of successive
+-- | /O(n)/. 'scanl' is similar to 'foldl', but returns a list of successive
 -- reduced values from the left:
 --
 -- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
@@ -300,7 +300,8 @@ constScanl :: a -> b -> a
 constScanl = const
 
 
--- | 'scanl1' is a variant of 'scanl' that has no starting value argument:
+-- | /O(n)/. 'scanl1' is a variant of 'scanl' that has no starting value
+-- argument:
 --
 -- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
 
@@ -308,7 +309,7 @@ scanl1                  :: (a -> a -> a) -> [a] -> [a]
 scanl1 f (x:xs)         =  scanl f x xs
 scanl1 _ []             =  []
 
--- | A strictly accumulating version of 'scanl'
+-- | /O(n)/. A strictly accumulating version of 'scanl'
 {-# NOINLINE [1] scanl' #-}
 scanl'           :: (b -> a -> b) -> b -> [a] -> [b]
 -- This peculiar form is needed to prevent scanl' from being rewritten
@@ -380,7 +381,7 @@ foldr1 f = go
         go []             =  errorEmptyList "foldr1"
 {-# INLINE [0] foldr1 #-}
 
--- | 'scanr' is the right-to-left dual of 'scanl'.
+-- | /O(n)/. 'scanr' is the right-to-left dual of 'scanl'.
 -- Note that
 --
 -- > head (scanr f z xs) == foldr f z xs.
@@ -407,7 +408,8 @@ scanrFB f c = \x (r, est) -> (f x r, r `c` est)
                  scanr f q0 ls
  #-}
 
--- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
+-- | /O(n)/. 'scanr1' is a variant of 'scanr' that has no starting value
+-- argument.
 scanr1                  :: (a -> a -> a) -> [a] -> [a]
 scanr1 _ []             =  []
 scanr1 _ [x]            =  [x]
@@ -975,7 +977,8 @@ foldr3_left _  z _ _  _      _     = z
 -- Zips for larger tuples are in the List module.
 
 ----------------------------------------------
--- | 'zip' takes two lists and returns a list of corresponding pairs.
+-- | /O(min(m,n))/. 'zip' takes two lists and returns a list of corresponding
+-- pairs.
 --
 -- > zip [1, 2] ['a', 'b'] = [(1, 'a'), (2, 'b')]
 --
@@ -1032,10 +1035,13 @@ zip3FB cons = \a b c r -> (a,b,c) `cons` r
 -- function given as the first argument, instead of a tupling function.
 
 ----------------------------------------------
--- | 'zipWith' generalises 'zip' by zipping with the function given
--- as the first argument, instead of a tupling function.
--- For example, @'zipWith' (+)@ is applied to two lists to produce the
--- list of corresponding sums.
+-- | /O(min(m,n))/. 'zipWith' generalises 'zip' by zipping with the function
+-- given as the first argument, instead of a tupling function. For example,
+-- @'zipWith' (+)@ is applied to two lists to produce the list of corresponding
+-- sums:
+--
+-- >>> zipWith (+) [1, 2, 3] [4, 5, 6]
+-- [5,7,9]
 --
 -- 'zipWith' is right-lazy:
 --



More information about the ghc-commits mailing list