summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorOleg Grenrus <oleg.grenrus@iki.fi>2020-12-28 15:04:51 +0200
committerHécate Moonlight <hecate+gitlab@glitchbra.in>2021-02-17 09:16:50 +0100
commit2d424a4632f7041926e0effdfb62de7557d52d24 (patch)
tree3709a47d054304987162b35ef9825fb850bcecfb
parent0ddf92585090704f9a98b4047febf2756b544a0f (diff)
downloadhaskell-2d424a4632f7041926e0effdfb62de7557d52d24.tar.gz
Correct more doctests
-rw-r--r--libraries/base/Data/Bifoldable.hs7
-rw-r--r--libraries/base/Data/Bifunctor.hs4
-rw-r--r--libraries/base/Data/Foldable.hs4
-rw-r--r--libraries/base/Data/Functor.hs2
-rw-r--r--libraries/base/Data/Traversable.hs12
-rw-r--r--libraries/base/GHC/Base.hs5
-rw-r--r--libraries/base/GHC/Float.hs3
-rw-r--r--libraries/base/GHC/List.hs29
-rw-r--r--libraries/base/Numeric.hs2
9 files changed, 48 insertions, 20 deletions
diff --git a/libraries/base/Data/Bifoldable.hs b/libraries/base/Data/Bifoldable.hs
index e29c18e767..1d057ee919 100644
--- a/libraries/base/Data/Bifoldable.hs
+++ b/libraries/base/Data/Bifoldable.hs
@@ -55,6 +55,13 @@ import Data.Maybe (fromMaybe)
import Data.Monoid
import GHC.Generics (K1(..))
+-- $setup
+-- >>> import Prelude
+-- >>> import Data.Char
+-- >>> import Data.Monoid (Product (..), Sum (..))
+-- >>> data BiList a b = BiList [a] [b]
+-- >>> instance Bifoldable BiList where bifoldr f g z (BiList as bs) = foldr f (foldr g z bs) as
+
-- | 'Bifoldable' identifies foldable structures with two different varieties
-- of elements (as opposed to 'Foldable', which has one variety of element).
-- Common examples are 'Either' and @(,)@:
diff --git a/libraries/base/Data/Bifunctor.hs b/libraries/base/Data/Bifunctor.hs
index 04de5ad7f2..e8cfe05979 100644
--- a/libraries/base/Data/Bifunctor.hs
+++ b/libraries/base/Data/Bifunctor.hs
@@ -20,6 +20,10 @@ module Data.Bifunctor
import Control.Applicative ( Const(..) )
import GHC.Generics ( K1(..) )
+-- $setup
+-- >>> import Prelude
+-- >>> import Data.Char (toUpper)
+
-- | A bifunctor is a type constructor that takes
-- two type arguments and is a functor in /both/ arguments. That
-- is, unlike with 'Functor', a type constructor such as 'Either'
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index c5cf09d20c..8e61c6a886 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -117,6 +117,10 @@ import GHC.Generics
import GHC.Tuple (Solo (..))
import GHC.Num ( Num(..) )
+-- $setup
+-- >>> import Prelude
+-- >>> import Data.Monoid (Product (..), Sum (..))
+
infix 4 `elem`, `notElem`
-- XXX: Missing haddock feature. Links to anchors in other modules
diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs
index e48c19e080..9689a0e798 100644
--- a/libraries/base/Data/Functor.hs
+++ b/libraries/base/Data/Functor.hs
@@ -25,7 +25,7 @@
-- Nothing -- (Int -> String) -> Maybe Int -> Maybe String
--
-- >>> fmap show [1,2,3] -- (a -> b) -> f a -> f b
--- ["1", "2", "3"] -- (Int -> String) -> [Int] -> [String]
+-- ["1","2","3"] -- (Int -> String) -> [Int] -> [String]
--
-- >>> fmap show [] -- (a -> b) -> f a -> f b
-- [] -- (Int -> String) -> [Int] -> [String]
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index 03283493e5..a17930dbc5 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -165,15 +165,9 @@ class (Functor t, Foldable t) => Traversable t where
--
-- ==== __Examples__
--
- -- 'mapM' is 'traverse' for 'Monad', and the following example shows
- -- how 'mapM' can apply an 'IO' action to a 'List' to produce a
- -- structured result.
- --
- -- Basic usage:
- --
- -- >>> import System.IO
- -- >>> mapM (openTempFile ".") ["t1", "t2"]
- -- [("./t169980-3",{handle: ./t169980-3}),("./t269980-4",{handle: ./t269980-4})]
+ -- 'mapM' is literally a 'traverse' with a type signature restricted
+ -- to 'Monad'. Its implementation may be more efficient due to additional
+ -- power of 'Monad'.
--
mapM :: Monad m => (a -> m b) -> t a -> m (t b)
{-# INLINE mapM #-} -- See Note [Inline default methods]
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 4af6a2bd73..0378df032b 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -131,6 +131,9 @@ import {-# SOURCE #-} Data.Semigroup.Internal ( stimesDefault
, stimesIdempotentMonoid
)
+-- $setup
+-- >>> import GHC.Num
+
infixr 9 .
infixr 5 ++
infixl 4 <$
@@ -218,7 +221,7 @@ class Semigroup a where
-- The default definition should be sufficient, but this can be
-- overridden for efficiency.
--
- -- >>> import Data.List.NonEmpty
+ -- >>> import Data.List.NonEmpty (NonEmpty (..))
-- >>> sconcat $ "Hello" :| [" ", "Haskell", "!"]
-- "Hello Haskell!"
sconcat :: NonEmpty a -> a
diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs
index bd9c505de0..0828198251 100644
--- a/libraries/base/GHC/Float.hs
+++ b/libraries/base/GHC/Float.hs
@@ -70,6 +70,9 @@ import GHC.Num.BigNat
infixr 8 **
+-- $setup
+-- >>> import Prelude
+
------------------------------------------------------------------------
-- Standard numeric classes
------------------------------------------------------------------------
diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs
index f3f2ad5909..34f338d67f 100644
--- a/libraries/base/GHC/List.hs
+++ b/libraries/base/GHC/List.hs
@@ -41,6 +41,17 @@ import GHC.Num.Integer (Integer)
infixl 9 !!
infix 4 `elem`, `notElem`
+-- $setup
+-- >>> import GHC.Base
+-- >>> import Prelude (Num (..), Ord (..), Int, Double, odd, not, undefined)
+-- >>> import Control.DeepSeq (force)
+--
+-- -- compiled versions are uninterruptible.
+-- https://gitlab.haskell.org/ghc/ghc/-/issues/367
+--
+-- >>> let or = foldr (||) False
+-- >>> let and = foldr (&&) True
+
--------------------------------------------------------------
-- List-manipulation functions
--------------------------------------------------------------
@@ -503,8 +514,8 @@ match on everything past the :, which is just the tail of scanl.
-- False
-- >>> foldr1 (||) [False, False, True, True]
-- True
--- >>> foldr1 (+) [1..]
--- * Hangs forever *
+-- >>> force $ foldr1 (+) [1..]
+-- *** Exception: stack overflow
foldr1 :: (a -> a -> a) -> [a] -> a
foldr1 f = go
where go [x] = x
@@ -590,7 +601,7 @@ remove the cause for the chain of evaluations, and all is well.
-- [False,False,True,True]
-- >>> scanr1 (||) [True, True, False, False]
-- [True,True,False,False]
--- >>> scanr1 (+) [1..]
+-- >>> force $ scanr1 (+) [1..]
-- * Hangs forever *
scanr1 :: (a -> a -> a) -> [a] -> [a]
scanr1 _ [] = []
@@ -653,9 +664,9 @@ minimum xs = foldl1 min xs
-- the consumer doesn't force each iterate. See 'iterate'' for a strict
-- variant of this function.
--
--- >>> iterate not True
+-- >>> take 10 $ iterate not True
-- [True,False,True,False...
--- >>> iterate (+3) 42
+-- >>> take 10 $ iterate (+3) 42
-- [42,45,48,51,54,57,60,63...
{-# NOINLINE [1] iterate #-}
iterate :: (a -> a) -> a -> [a]
@@ -698,7 +709,7 @@ iterate'FB c f x0 = go x0
-- | 'repeat' @x@ is an infinite list, with @x@ the value of every element.
--
--- >>> repeat 17
+-- >>> take 20 $ repeat 17
--[17,17,17,17,17,17,17,17,17...
repeat :: a -> [a]
{-# INLINE [0] repeat #-}
@@ -735,10 +746,10 @@ replicate n x = take n (repeat x)
-- on infinite lists.
--
-- >>> cycle []
--- Exception: Prelude.cycle: empty list
--- >>> cycle [42]
+-- *** Exception: Prelude.cycle: empty list
+-- >>> take 20 $ cycle [42]
-- [42,42,42,42,42,42,42,42,42,42...
--- >>> cycle [2, 5, 7]
+-- >>> take 20 $ cycle [2, 5, 7]
-- [2,5,7,2,5,7,2,5,7,2,5,7...
cycle :: [a] -> [a]
cycle [] = errorEmptyList "cycle"
diff --git a/libraries/base/Numeric.hs b/libraries/base/Numeric.hs
index 00e5f674de..afc83613f6 100644
--- a/libraries/base/Numeric.hs
+++ b/libraries/base/Numeric.hs
@@ -70,6 +70,8 @@ import GHC.Show
import Text.ParserCombinators.ReadP( ReadP, readP_to_S, pfail )
import qualified Text.Read.Lex as L
+-- $setup
+-- >>> import Prelude
-- -----------------------------------------------------------------------------
-- Reading