summaryrefslogtreecommitdiff
path: root/libraries/base/Data
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/Data')
-rw-r--r--libraries/base/Data/Foldable.hs3
-rw-r--r--libraries/base/Data/Function.hs25
-rw-r--r--libraries/base/Data/Proxy.hs39
-rw-r--r--libraries/base/Data/STRef.hs26
-rw-r--r--libraries/base/Data/Unique.hs11
5 files changed, 94 insertions, 10 deletions
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index 1d9fc92ca5..e33d45efcf 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -506,6 +506,9 @@ sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
sequence_ = foldr (>>) (return ())
-- | The sum of a collection of actions, generalizing 'concat'.
+--
+-- asum [Just "Hello", Nothing, Just "World"]
+-- Just "Hello"
asum :: (Foldable t, Alternative f) => t (f a) -> f a
{-# INLINE asum #-}
asum = foldr (<|>) empty
diff --git a/libraries/base/Data/Function.hs b/libraries/base/Data/Function.hs
index c5ded4cda5..ccc58c74ac 100644
--- a/libraries/base/Data/Function.hs
+++ b/libraries/base/Data/Function.hs
@@ -32,13 +32,28 @@ infixl 1 &
-- | @'fix' f@ is the least fixed point of the function @f@,
-- i.e. the least defined @x@ such that @f x = x@.
+--
+-- For example, we can write the factorial function using direct recursion as
+--
+-- >>> let fac n = if n <= 1 then 1 else n * fac (n-1) in fac 5
+-- 120
+--
+-- This uses the fact that Haskell’s @let@ introduces recursive bindings. We can
+-- rewrite this definition using 'fix',
+--
+-- >>> fix (\rec n -> if n <= 1 then 1 else n * rec (n-1)) 5
+-- 120
+--
+-- Instead of making a recursive call, we introduce a dummy parameter @rec@;
+-- when used within 'fix', this parameter then refers to 'fix'' argument, hence
+-- the recursion is reintroduced.
fix :: (a -> a) -> a
fix f = let x = f x in x
--- | @(*) \`on\` f = \\x y -> f x * f y@.
+-- | @((==) \`on\` f) x y = f x == f y@
--
-- Typical usage: @'Data.List.sortBy' ('compare' \`on\` 'fst')@.
---
+
-- Algebraic properties:
--
-- * @(*) \`on\` 'id' = (*)@ (if @(*) &#x2209; {&#x22a5;, 'const' &#x22a5;}@)
@@ -95,6 +110,12 @@ on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
-- convenience. Its precedence is one higher than that of the forward
-- application operator '$', which allows '&' to be nested in '$'.
--
+-- >>> 5 & (+1) & show
+-- "6"
+--
-- @since 4.8.0.0
(&) :: a -> (a -> b) -> b
x & f = f x
+
+-- $setup
+-- >>> import Prelude
diff --git a/libraries/base/Data/Proxy.hs b/libraries/base/Data/Proxy.hs
index d6f03548f3..1ebf56c9a5 100644
--- a/libraries/base/Data/Proxy.hs
+++ b/libraries/base/Data/Proxy.hs
@@ -28,7 +28,31 @@ import GHC.Read
import GHC.Enum
import GHC.Arr
--- | A concrete, poly-kinded proxy type
+-- $setup
+-- >>> import Data.Void
+-- >>> import Prelude
+
+-- | 'Proxy' is a type that holds no data, but has a phantom parameter of
+-- arbitrary type (or even kind). Its use is to provide type information, even
+-- though there is no value available of that type (or it may be too costly to
+-- create one).
+--
+-- Historically, @'Proxy' :: 'Proxy' a@ is a safer alternative to the
+-- @'undefined :: a'@ idiom.
+--
+-- >>> Proxy :: Proxy (Void, Int -> Int)
+-- Proxy
+--
+-- Proxy can even hold types of higher kinds,
+--
+-- >>> Proxy :: Proxy Either
+-- Proxy
+--
+-- >>> Proxy :: Proxy Functor
+-- Proxy
+--
+-- >>> Proxy :: Proxy complicatedStructure
+-- Proxy
data Proxy t = Proxy deriving Bounded
-- | A concrete, promotable proxy type, for use at the kind level
@@ -113,6 +137,19 @@ instance MonadPlus Proxy
-- It is usually used as an infix operator, and its typing forces its first
-- argument (which is usually overloaded) to have the same type as the tag
-- of the second.
+--
+-- >>> import Data.Word
+-- >>> :type asProxyTypeOf 123 (Proxy :: Proxy Word8)
+-- asProxyTypeOf 123 (Proxy :: Proxy Word8) :: Word8
+--
+-- Note the lower-case @proxy@ in the definition. This allows any type
+-- constructor with just one argument to be passed to the function, for example
+-- we could also write
+--
+-- >>> import Data.Word
+-- >>> :type asProxyTypeOf 123 (Just (undefined :: Word8))
+-- asProxyTypeOf 123 (Just (undefined :: Word8)) :: Word8
asProxyTypeOf :: a -> proxy a -> a
asProxyTypeOf = const
{-# INLINE asProxyTypeOf #-}
+
diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs
index 60bccf50cb..46ca08361b 100644
--- a/libraries/base/Data/STRef.hs
+++ b/libraries/base/Data/STRef.hs
@@ -5,7 +5,7 @@
-- Module : Data.STRef
-- Copyright : (c) The University of Glasgow 2001
-- License : BSD-style (see the file libraries/base/LICENSE)
---
+--
-- Maintainer : libraries@haskell.org
-- Stability : experimental
-- Portability : non-portable (uses Control.Monad.ST)
@@ -29,16 +29,30 @@ import GHC.STRef
-- | Mutate the contents of an 'STRef'.
--
+-- >>> :{
+-- runST (do
+-- ref <- newSTRef ""
+-- modifySTRef ref (const "world")
+-- modifySTRef ref (++ "!")
+-- modifySTRef ref ("Hello, " ++)
+-- readSTRef ref )
+-- :}
+-- "Hello, world!"
+--
-- Be warned that 'modifySTRef' does not apply the function strictly. This
-- means if the program calls 'modifySTRef' many times, but seldomly uses the
-- value, thunks will pile up in memory resulting in a space leak. This is a
-- common mistake made when using an STRef as a counter. For example, the
--- following will leak memory and likely produce a stack overflow:
+-- following will leak memory and may produce a stack overflow:
--
--- >print $ runST $ do
--- > ref <- newSTRef 0
--- > replicateM_ 1000000 $ modifySTRef ref (+1)
--- > readSTRef ref
+-- >>> import Control.Monad (replicateM_)
+-- >>> :{
+-- print (runST (do
+-- ref <- newSTRef 0
+-- replicateM_ 1000 $ modifySTRef ref (+1)
+-- readSTRef ref ))
+-- :}
+-- 1000
--
-- To avoid this problem, use 'modifySTRef'' instead.
modifySTRef :: STRef s a -> (a -> a) -> ST s ()
diff --git a/libraries/base/Data/Unique.hs b/libraries/base/Data/Unique.hs
index 2db9247572..eef6256395 100644
--- a/libraries/base/Data/Unique.hs
+++ b/libraries/base/Data/Unique.hs
@@ -6,7 +6,7 @@
-- Module : Data.Unique
-- Copyright : (c) The University of Glasgow 2001
-- License : BSD-style (see the file libraries/base/LICENSE)
---
+--
-- Maintainer : libraries@haskell.org
-- Stability : experimental
-- Portability : non-portable
@@ -30,6 +30,15 @@ import Data.IORef
-- | An abstract unique object. Objects of type 'Unique' may be
-- compared for equality and ordering and hashed into 'Int'.
+--
+-- >>> :{
+-- do x <- newUnique
+-- print (x == x)
+-- y <- newUnique
+-- print (x == y)
+-- :}
+-- True
+-- False
newtype Unique = Unique Integer deriving (Eq,Ord)
uniqSource :: IORef Integer