summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--libraries/base/Control/Applicative.hs7
-rw-r--r--libraries/base/Control/Monad.hs10
-rw-r--r--libraries/base/Data/Bifoldable.hs12
-rw-r--r--libraries/base/Data/Bifunctor.hs3
-rw-r--r--libraries/base/Data/Bitraversable.hs5
-rw-r--r--libraries/base/Data/Bool.hs3
-rw-r--r--libraries/base/Data/Either.hs2
-rw-r--r--libraries/base/Data/Maybe.hs3
-rw-r--r--libraries/base/Data/Monoid.hs2
-rw-r--r--libraries/base/Data/Ord.hs3
-rw-r--r--libraries/base/Data/STRef.hs4
-rw-r--r--libraries/base/Data/Semigroup.hs11
-rw-r--r--libraries/base/Data/Traversable.hs3
-rw-r--r--libraries/base/Data/Unique.hs3
-rw-r--r--libraries/base/Data/Void.hs3
-rw-r--r--libraries/base/Debug/Trace.hs11
-rw-r--r--libraries/base/GHC/Float.hs3
-rw-r--r--libraries/base/GHC/List.hs41
-rw-r--r--libraries/base/GHC/STRef.hs3
-rw-r--r--libraries/base/GHC/Stack/Types.hs10
-rw-r--r--libraries/base/GHC/Unicode.hs3
-rw-r--r--libraries/base/System/Timeout.hs4
-rw-r--r--libraries/base/Text/Printf.hs3
-rw-r--r--libraries/base/Text/Read.hs3
24 files changed, 117 insertions, 38 deletions
diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs
index 6c05eec843..93022cb29c 100644
--- a/libraries/base/Control/Applicative.hs
+++ b/libraries/base/Control/Applicative.hs
@@ -63,6 +63,9 @@ import GHC.List (repeat, zipWith, drop)
import GHC.Read (Read)
import GHC.Show (Show)
+-- $setup
+-- >>> import Prelude
+
newtype WrappedMonad m a = WrapMonad { unwrapMonad :: m a }
deriving ( Generic -- ^ @since 4.7.0.0
, Generic1 -- ^ @since 4.7.0.0
@@ -146,7 +149,9 @@ instance Alternative ZipList where
--
-- ==== __Examples__
--
--- Using the 'Alternative' instance of `Control.Monad.Except`, the following functions:
+-- Using the 'Alternative' instance of "Control.Monad.Except", the following functions:
+--
+-- >>> import Control.Monad.Except
--
-- >>> canFail = throwError "it failed" :: Except String Int
-- >>> final = return 42 :: Except String Int
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index c906014cd0..b4f2cc022d 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -85,6 +85,10 @@ import GHC.Base hiding ( mapM, sequence )
import GHC.List ( zipWith, unzip )
import GHC.Num ( (-) )
+-- $setup
+-- >>> import Prelude
+-- >>> let safeDiv x y = guard (y /= 0) >> Just (x `div` y :: Int)
+
-- -----------------------------------------------------------------------------
-- Functions mandated by the Prelude
@@ -106,12 +110,11 @@ import GHC.Num ( (-) )
-- 'Nothing' when the denominator @y@ is zero and @'Just' (x \`div\`
-- y)@ otherwise. For example:
--
--- @
-- >>> safeDiv 4 0
-- Nothing
+--
-- >>> safeDiv 4 2
-- Just 2
--- @
--
-- A definition of @safeDiv@ using guards, but not 'guard':
--
@@ -360,12 +363,11 @@ f <$!> m = do
--
-- An example using 'mfilter' with the 'Maybe' monad:
--
--- @
-- >>> mfilter odd (Just 1)
-- Just 1
-- >>> mfilter odd (Just 2)
-- Nothing
--- @
+--
mfilter :: (MonadPlus m) => (a -> Bool) -> m a -> m a
{-# INLINABLE mfilter #-}
mfilter p ma = do
diff --git a/libraries/base/Data/Bifoldable.hs b/libraries/base/Data/Bifoldable.hs
index e29c18e767..977d63d3b8 100644
--- a/libraries/base/Data/Bifoldable.hs
+++ b/libraries/base/Data/Bifoldable.hs
@@ -55,6 +55,12 @@ import Data.Maybe (fromMaybe)
import Data.Monoid
import GHC.Generics (K1(..))
+-- $setup
+-- >>> import Prelude
+-- >>> import Data.Char
+-- >>> 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 @(,)@:
@@ -288,6 +294,7 @@ bifoldr' f g z0 xs = bifoldl f' g' id xs z0 where
--
-- >>> bifoldr1 (+) (BiList [] [])
-- *** Exception: bifoldr1: empty structure
+-- ...
--
-- @since 4.10.0.0
bifoldr1 :: Bifoldable t => (a -> a -> a) -> t a a -> a
@@ -349,6 +356,7 @@ bifoldl' f g z0 xs = bifoldr f' g' id xs z0 where
--
-- >>> bifoldl1 (+) (BiList [] [])
-- *** Exception: bifoldl1: empty structure
+-- ...
--
-- @since 4.10.0.0
bifoldl1 :: Bifoldable t => (a -> a -> a) -> t a a -> a
@@ -633,6 +641,7 @@ biconcat = bifold
--
-- >>> bimaximum (BiList [] [])
-- *** Exception: bimaximum: empty structure
+-- ...
--
-- @since 4.10.0.0
bimaximum :: forall t a. (Bifoldable t, Ord a) => t a a -> a
@@ -662,6 +671,7 @@ bimaximum = fromMaybe (error "bimaximum: empty structure") .
--
-- >>> biminimum (BiList [] [])
-- *** Exception: biminimum: empty structure
+-- ...
--
-- @since 4.10.0.0
biminimum :: forall t a. (Bifoldable t, Ord a) => t a a -> a
@@ -915,6 +925,7 @@ biall p q = getAll #. bifoldMap (All . p) (All . q)
--
-- >>> bimaximumBy compare (BiList [] [])
-- *** Exception: bifoldr1: empty structure
+-- ...
--
-- @since 4.10.0.0
bimaximumBy :: Bifoldable t => (a -> a -> Ordering) -> t a a -> a
@@ -943,6 +954,7 @@ bimaximumBy cmp = bifoldr1 max'
--
-- >>> biminimumBy compare (BiList [] [])
-- *** Exception: bifoldr1: empty structure
+-- ...
--
-- @since 4.10.0.0
biminimumBy :: Bifoldable t => (a -> a -> Ordering) -> t a a -> a
diff --git a/libraries/base/Data/Bifunctor.hs b/libraries/base/Data/Bifunctor.hs
index 04de5ad7f2..92d235da30 100644
--- a/libraries/base/Data/Bifunctor.hs
+++ b/libraries/base/Data/Bifunctor.hs
@@ -20,6 +20,9 @@ module Data.Bifunctor
import Control.Applicative ( Const(..) )
import GHC.Generics ( K1(..) )
+-- $setup
+-- >>> import Prelude
+
-- | 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/Bitraversable.hs b/libraries/base/Data/Bitraversable.hs
index 0d34e2710c..b0278a00c5 100644
--- a/libraries/base/Data/Bitraversable.hs
+++ b/libraries/base/Data/Bitraversable.hs
@@ -34,6 +34,11 @@ import Data.Functor.Identity (Identity(..))
import Data.Functor.Utils (StateL(..), StateR(..))
import GHC.Generics (K1(..))
+-- $setup
+-- >>> import Prelude
+-- >>> import Data.Maybe
+-- >>> import Data.List (find)
+
-- | 'Bitraversable' identifies bifunctorial data structures whose elements can
-- be traversed in order, performing 'Applicative' or 'Monad' actions at each
-- element, and collecting a result structure with the same shape.
diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs
index 3e812d41b4..4e2bff30e2 100644
--- a/libraries/base/Data/Bool.hs
+++ b/libraries/base/Data/Bool.hs
@@ -28,6 +28,9 @@ module Data.Bool (
import GHC.Base
+-- $setup
+-- >>> import Prelude
+
-- | Case analysis for the 'Bool' type. @'bool' x y p@ evaluates to @x@
-- when @p@ is 'False', and evaluates to @y@ when @p@ is 'True'.
--
diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs
index 8e63017db8..3fd2ac8467 100644
--- a/libraries/base/Data/Either.hs
+++ b/libraries/base/Data/Either.hs
@@ -38,7 +38,7 @@ import GHC.Read
-- $setup
-- Allow the use of some Prelude functions in doctests.
--- >>> import Prelude ( (+), (*), length, putStrLn )
+-- >>> import Prelude
{-
-- just for testing
diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs
index 8c46cfba8b..acce0bef52 100644
--- a/libraries/base/Data/Maybe.hs
+++ b/libraries/base/Data/Maybe.hs
@@ -36,7 +36,7 @@ import GHC.Stack.Types ( HasCallStack )
-- $setup
-- Allow the use of some Prelude functions in doctests.
--- >>> import Prelude ( (*), odd, show, sum )
+-- >>> import Prelude
-- ---------------------------------------------------------------------------
-- Functions over Maybe
@@ -143,6 +143,7 @@ isNothing _ = False
--
-- >>> 2 * (fromJust Nothing)
-- *** Exception: Maybe.fromJust: Nothing
+-- ...
--
fromJust :: HasCallStack => Maybe a -> a
fromJust Nothing = error "Maybe.fromJust: Nothing" -- yuck
diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs
index 479dac88f5..30c7b988b8 100644
--- a/libraries/base/Data/Monoid.hs
+++ b/libraries/base/Data/Monoid.hs
@@ -30,7 +30,7 @@
-- The 'Sum' monoid is defined by the numerical addition operator and `0` as neutral element:
--
-- >>> mempty :: Sum Int
--- Sum 0
+-- Sum {getSum = 0}
-- >>> Sum 1 <> Sum 2 <> Sum 3 <> Sum 4 :: Sum Int
-- Sum {getSum = 10}
--
diff --git a/libraries/base/Data/Ord.hs b/libraries/base/Data/Ord.hs
index 7628e017b6..cf95d69389 100644
--- a/libraries/base/Data/Ord.hs
+++ b/libraries/base/Data/Ord.hs
@@ -35,6 +35,9 @@ import GHC.Read
import GHC.Real (Fractional, Real, RealFrac)
import GHC.Show
+-- $setup
+-- >>> import Prelude
+
-- |
-- > comparing p x y = compare (p x) (p y)
--
diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs
index 3636e6a8a6..e3d9401729 100644
--- a/libraries/base/Data/STRef.hs
+++ b/libraries/base/Data/STRef.hs
@@ -27,6 +27,10 @@ module Data.STRef (
import GHC.ST
import GHC.STRef
+-- $setup
+-- >>> import Prelude
+-- >>> import Control.Monad.ST
+
-- | Mutate the contents of an 'STRef'.
--
-- >>> :{
diff --git a/libraries/base/Data/Semigroup.hs b/libraries/base/Data/Semigroup.hs
index 54a0a61ed6..aaabe97e71 100644
--- a/libraries/base/Data/Semigroup.hs
+++ b/libraries/base/Data/Semigroup.hs
@@ -20,7 +20,7 @@
-- that lets you combine any two values of type @a@ into one. Where being
-- associative means that the following must always hold:
--
--- >>> (a <> b) <> c == a <> (b <> c)
+-- prop> (a <> b) <> c == a <> (b <> c)
--
-- ==== __Examples__
--
@@ -36,9 +36,10 @@
-- can never be empty:
--
-- >>> (1 :| [])
--- 1 :| [] -- equivalent to [1] but guaranteed to be non-empty
+-- 1 :| [] -- equivalent to [1] but guaranteed to be non-empty.
+--
-- >>> (1 :| [2, 3, 4])
--- 1 :| [2,3,4] -- equivalent to [1,2,3,4] but guaranteed to be non-empty
+-- 1 :| [2,3,4] -- equivalent to [1,2,3,4] but guaranteed to be non-empty.
--
-- Equipped with this guaranteed to be non-empty data structure, we can combine
-- values using 'sconcat' and a 'Semigroup' of our choosing. We can try the 'Min'
@@ -116,6 +117,10 @@ import Data.Coerce
import Data.Data
import GHC.Generics
+-- $setup
+-- >>> import Prelude
+-- >>> import Data.List.NonEmpty (NonEmpty (..))
+
-- | A generalization of 'Data.List.cycle' to an arbitrary 'Semigroup'.
-- May fail to terminate for some values in some semigroups.
cycle1 :: Semigroup m => m -> m
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index 7d37be003a..b2cd20f0ac 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -79,6 +79,9 @@ import GHC.Base ( Applicative(..), Monad(..), Monoid, Maybe(..), NonEmpty(..),
import GHC.Generics
import qualified GHC.List as List ( foldr )
+-- $setup
+-- >>> import Prelude
+
-- | Functors representing data structures that can be traversed from
-- left to right.
--
diff --git a/libraries/base/Data/Unique.hs b/libraries/base/Data/Unique.hs
index 95b94102d1..c14b063b3b 100644
--- a/libraries/base/Data/Unique.hs
+++ b/libraries/base/Data/Unique.hs
@@ -26,6 +26,9 @@ import System.IO.Unsafe (unsafePerformIO)
import GHC.Num
import Data.IORef
+-- $setup
+-- >>> import Prelude
+
-- | An abstract unique object. Objects of type 'Unique' may be
-- compared for equality and ordering and hashed into 'Int'.
--
diff --git a/libraries/base/Data/Void.hs b/libraries/base/Data/Void.hs
index 7558308cd3..380720d6ee 100644
--- a/libraries/base/Data/Void.hs
+++ b/libraries/base/Data/Void.hs
@@ -30,6 +30,9 @@ import Data.Ix
import GHC.Generics
import Data.Semigroup (Semigroup(..), stimesIdempotent)
+-- $setup
+-- >>> import Prelude
+
-- | Uninhabited data type
--
-- @since 4.8.0.0
diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs
index 5a8b55126c..e85fb7590a 100644
--- a/libraries/base/Debug/Trace.hs
+++ b/libraries/base/Debug/Trace.hs
@@ -106,12 +106,13 @@ putTraceMsg = traceIO
The 'trace' function outputs the trace message given as its first argument,
before returning the second argument as its result.
-For example, this returns the value of @f x@ but first outputs the message.
+For example, this returns the value of @f x@ and outputs the message to stderr.
+Depending on your terminal (settings), they may or may not be mixed.
>>> let x = 123; f = show
>>> trace ("calling f with x = " ++ show x) (f x)
-"calling f with x = 123
-123"
+calling f with x = 123
+"123"
The 'trace' function should /only/ be used for debugging, or for monitoring
execution. The function is not referentially transparent: its type indicates
@@ -127,8 +128,8 @@ trace string expr = unsafePerformIO $ do
Like 'trace' but returns the message instead of a third value.
>>> traceId "hello"
-"hello
-hello"
+hello
+"hello"
@since 4.7.0.0
-}
diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs
index 5b859b1db9..10e0539c11 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 GHC.Num
+
------------------------------------------------------------------------
-- Standard numeric classes
------------------------------------------------------------------------
diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs
index cd7ffc6637..dc8f95eb5b 100644
--- a/libraries/base/GHC/List.hs
+++ b/libraries/base/GHC/List.hs
@@ -41,6 +41,9 @@ import GHC.Num.Integer (Integer)
infixl 9 !!
infix 4 `elem`, `notElem`
+-- $setup
+-- >>> import Prelude (Num (..), Ord (..), Int, Double, odd, not, undefined)
+
--------------------------------------------------------------
-- List-manipulation functions
--------------------------------------------------------------
@@ -52,7 +55,7 @@ infix 4 `elem`, `notElem`
-- >>> head [1..]
-- 1
-- >>> head []
--- Exception: Prelude.head: empty list
+-- *** Exception: Prelude.head: empty list
head :: [a] -> a
head (x:_) = x
head [] = badHead
@@ -96,7 +99,7 @@ uncons (x:xs) = Just (x, xs)
-- >>> tail [1]
-- []
-- >>> tail []
--- Exception: Prelude.tail: empty list
+-- *** Exception: Prelude.tail: empty list
tail :: [a] -> [a]
tail (_:xs) = xs
tail [] = errorEmptyList "tail"
@@ -109,7 +112,7 @@ tail [] = errorEmptyList "tail"
-- >>> last [1..]
-- * Hangs forever *
-- >>> last []
--- Exception: Prelude.last: empty list
+-- *** Exception: Prelude.last: empty list
last :: [a] -> a
#if defined(USE_REPORT_PRELUDE)
last [x] = x
@@ -135,7 +138,7 @@ lastError = errorEmptyList "last"
-- >>> init [1]
-- []
-- >>> init []
--- Exception: Prelude.init: empty list
+-- *** Exception: Prelude.init: empty list
init :: [a] -> [a]
#if defined(USE_REPORT_PRELUDE)
init [x] = []
@@ -305,7 +308,7 @@ foldl' k z0 xs =
-- >>> foldl1 (+) [1..4]
-- 10
-- >>> foldl1 (+) []
--- Exception: Prelude.foldl1: empty list
+-- *** Exception: Prelude.foldl1: empty list
-- >>> foldl1 (-) [1..4]
-- -8
-- >>> foldl1 (&&) [True, False, True, True]
@@ -496,7 +499,7 @@ match on everything past the :, which is just the tail of scanl.
-- >>> foldr1 (+) [1..4]
-- 10
-- >>> foldr1 (+) []
--- Exception: Prelude.foldr1: empty list
+-- *** Exception: Prelude.foldr1: empty list
-- >>> foldr1 (-) [1..4]
-- -2
-- >>> foldr1 (&&) [True, False, True, True]
@@ -604,7 +607,7 @@ scanr1 f (x:xs) = f x q : qs
-- programmer to supply their own comparison function.
--
-- >>> maximum []
--- Exception: Prelude.maximum: empty list
+-- *** Exception: Prelude.maximum: empty list
-- >>> maximum [42]
-- 42
-- >>> maximum [55, -12, 7, 0, -89]
@@ -628,7 +631,7 @@ maximum xs = foldl1' max xs
-- programmer to supply their own comparison function.
--
-- >>> minimum []
--- Exception: Prelude.minimum: empty list
+-- *** Exception: Prelude.minimum: empty list
-- >>> minimum [42]
-- 42
-- >>> minimum [55, -12, 7, 0, -89]
@@ -735,7 +738,7 @@ replicate n x = take n (repeat x)
-- on infinite lists.
--
-- >>> cycle []
--- Exception: Prelude.cycle: empty list
+-- *** Exception: Prelude.cycle: empty list
-- >>> cycle [42]
-- [42,42,42,42,42,42,42,42,42,42...
-- >>> cycle [2, 5, 7]
@@ -1242,9 +1245,9 @@ concat = foldr (++) []
-- >>> ['a', 'b', 'c'] !! 2
-- 'c'
-- >>> ['a', 'b', 'c'] !! 3
--- Exception: Prelude.!!: index too large
+-- *** Exception: Prelude.!!: index too large
-- >>> ['a', 'b', 'c'] !! (-1)
--- Exception: Prelude.!!: negative index
+-- *** Exception: Prelude.!!: negative index
(!!) :: [a] -> Int -> a
#if defined(USE_REPORT_PRELUDE)
xs !! n | n < 0 = errorWithoutStackTrace "Prelude.!!: negative index"
@@ -1372,15 +1375,15 @@ NB: Zips for larger tuples are in the List module.
-- corresponding pairs.
--
-- >>> zip [1, 2] ['a', 'b']
--- [(1, 'a'), (2, 'b')]
+-- [(1,'a'),(2,'b')]
--
-- If one input list is shorter than the other, excess elements of the longer
-- list are discarded, even if one of the lists is infinite:
--
-- >>> zip [1] ['a', 'b']
--- [(1, 'a')]
+-- [(1,'a')]
-- >>> zip [1, 2] ['a']
--- [(1, 'a')]
+-- [(1,'a')]
-- >>> zip [] [1..]
-- []
-- >>> zip [1..] []
@@ -1388,10 +1391,11 @@ NB: Zips for larger tuples are in the List module.
--
-- 'zip' is right-lazy:
--
--- >>> zip [] _|_
+-- >>> zip [] undefined
-- []
--- >>> zip _|_ []
--- _|_
+-- >>> zip undefined []
+-- *** Exception: Prelude.undefined
+-- ...
--
-- 'zip' is capable of list fusion, but it is restricted to its
-- first list argument and its resulting list.
@@ -1449,7 +1453,8 @@ zip3FB cons = \a b c r -> (a,b,c) `cons` r
--
-- 'zipWith' is right-lazy:
--
--- >>> zipWith f [] _|_
+-- >>> let f = undefined
+-- >>> zipWith f [] undefined
-- []
--
-- 'zipWith' is capable of list fusion, but it is restricted to its
diff --git a/libraries/base/GHC/STRef.hs b/libraries/base/GHC/STRef.hs
index d3bedee9ef..f5a90900df 100644
--- a/libraries/base/GHC/STRef.hs
+++ b/libraries/base/GHC/STRef.hs
@@ -25,7 +25,8 @@ import GHC.ST
import GHC.Base
-- $setup
--- import Prelude
+-- >>> import Prelude
+-- >>> import Control.Monad.ST
data STRef s a = STRef (MutVar# s a)
-- ^ a value of type @STRef s a@ is a mutable variable in state thread @s@,
diff --git a/libraries/base/GHC/Stack/Types.hs b/libraries/base/GHC/Stack/Types.hs
index 4144448e96..8c729a693f 100644
--- a/libraries/base/GHC/Stack/Types.hs
+++ b/libraries/base/GHC/Stack/Types.hs
@@ -53,6 +53,10 @@ import GHC.Types (Char, Int)
import GHC.Tuple () -- See Note [Depend on GHC.Tuple] in GHC.Base
import GHC.Num.Integer () -- See Note [Depend on GHC.Num.Integer] in GHC.Base
+-- $setup
+-- >>> import Prelude
+-- >>> import GHC.Stack (prettyCallStack, callStack)
+
----------------------------------------------------------------------
-- Explicit call-stacks built via ImplicitParams
----------------------------------------------------------------------
@@ -81,12 +85,12 @@ type HasCallStack = (?callStack :: CallStack)
-- along with the string given as argument. We can access the
-- call-stack inside @putStrLnWithCallStack@ with 'GHC.Stack.callStack'.
--
--- @
+-- >>> :{
-- putStrLnWithCallStack :: HasCallStack => String -> IO ()
-- putStrLnWithCallStack msg = do
-- putStrLn msg
-- putStrLn (prettyCallStack callStack)
--- @
+-- :}
--
-- Thus, if we call @putStrLnWithCallStack@ we will get a formatted call-stack
-- alongside our string.
@@ -95,7 +99,7 @@ type HasCallStack = (?callStack :: CallStack)
-- >>> putStrLnWithCallStack "hello"
-- hello
-- CallStack (from HasCallStack):
--- putStrLnWithCallStack, called at <interactive>:2:1 in interactive:Ghci1
+-- putStrLnWithCallStack, called at <interactive>:... in interactive:Ghci...
--
--
-- GHC solves 'HasCallStack' constraints in three steps:
diff --git a/libraries/base/GHC/Unicode.hs b/libraries/base/GHC/Unicode.hs
index a3fcbf55f4..21ec66c8c1 100644
--- a/libraries/base/GHC/Unicode.hs
+++ b/libraries/base/GHC/Unicode.hs
@@ -45,6 +45,9 @@ import {-# SOURCE #-} Data.Version
-- for GeneralCategory
import GHC.Show ( Show )
+-- $setup
+-- >>> import Prelude
+
#include "HsBaseConfig.h"
#include "UnicodeVersion.h"
diff --git a/libraries/base/System/Timeout.hs b/libraries/base/System/Timeout.hs
index cc89bfed40..cfddccce3f 100644
--- a/libraries/base/System/Timeout.hs
+++ b/libraries/base/System/Timeout.hs
@@ -30,6 +30,10 @@ import Control.Exception (Exception(..), handleJust, bracket,
asyncExceptionFromException)
import Data.Unique (Unique, newUnique)
+-- $setup
+-- >>> import Prelude
+-- >>> import Control.Concurrent (threadDelay)
+
-- An internal type that is thrown as a dynamic exception to
-- interrupt the running IO computation when the timeout has
-- expired.
diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs
index 216c29d9e3..4fa9fd7720 100644
--- a/libraries/base/Text/Printf.hs
+++ b/libraries/base/Text/Printf.hs
@@ -100,6 +100,9 @@ import Numeric
import Numeric.Natural
import System.IO
+-- $setup
+-- >>> import Prelude
+
-------------------
-- | Format a variable number of arguments with the C-style formatting string.
diff --git a/libraries/base/Text/Read.hs b/libraries/base/Text/Read.hs
index c79b7c15b2..1e852a090c 100644
--- a/libraries/base/Text/Read.hs
+++ b/libraries/base/Text/Read.hs
@@ -51,6 +51,9 @@ import Text.ParserCombinators.ReadP as P
import Text.ParserCombinators.ReadPrec
import qualified Text.Read.Lex as L
+-- $setup
+-- >>> import Prelude
+
------------------------------------------------------------------------
-- utility functions