summaryrefslogtreecommitdiff
path: root/libraries
diff options
context:
space:
mode:
authorHerbert Valerio Riedel <hvr@gnu.org>2013-09-21 18:04:19 +0200
committerHerbert Valerio Riedel <hvr@gnu.org>2013-09-21 18:07:25 +0200
commit2642d9f6eac5879c7d38bc51726bede1bef77df4 (patch)
treed35215ec3086549a77a05fc273be678e3646c327 /libraries
parent77f32dad3bef5b641a9d15f69ad2e0f058ade67a (diff)
downloadhaskell-2642d9f6eac5879c7d38bc51726bede1bef77df4.tar.gz
Add Haddock `/Since: 4.6.0.0/` comments to symbols
This commit retroactively adds `/Since: 4.6.0.0/` annotations to symbols newly added/exposed in `base-4.6.0.0` (as shipped with GHC 7.6.1). See also 6368362f which adds the respective annotation for symbols newly added in `base-4.7.0.0` (that goes together with GHC 7.8.1). Signed-off-by: Herbert Valerio Riedel <hvr@gnu.org>
Diffstat (limited to 'libraries')
-rw-r--r--libraries/base/Control/Concurrent.hs1
-rw-r--r--libraries/base/Control/Concurrent/MVar.hs6
-rw-r--r--libraries/base/Data/Bits.hs6
-rw-r--r--libraries/base/Data/IORef.hs6
-rw-r--r--libraries/base/Data/Ord.hs2
-rw-r--r--libraries/base/Data/STRef.hs2
-rw-r--r--libraries/base/GHC/Conc/Sync.lhs1
-rw-r--r--libraries/base/GHC/Exception.lhs2
-rw-r--r--libraries/base/GHC/Generics.hs3
-rw-r--r--libraries/base/GHC/IP.hs2
-rw-r--r--libraries/base/GHC/Stats.hsc4
-rw-r--r--libraries/base/GHC/TypeLits.hs5
-rw-r--r--libraries/base/System/Environment.hs2
-rw-r--r--libraries/base/System/Environment/ExecutablePath.hsc3
-rw-r--r--libraries/base/Text/Read.hs4
-rw-r--r--libraries/base/Text/Read/Lex.hs2
16 files changed, 48 insertions, 3 deletions
diff --git a/libraries/base/Control/Concurrent.hs b/libraries/base/Control/Concurrent.hs
index ce081661aa..5637db5a0f 100644
--- a/libraries/base/Control/Concurrent.hs
+++ b/libraries/base/Control/Concurrent.hs
@@ -196,6 +196,7 @@ attribute will block all other threads.
-- This function is useful for informing the parent when a child
-- terminates, for example.
--
+-- /Since: 4.6.0.0/
forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
forkFinally action and_then =
mask $ \restore ->
diff --git a/libraries/base/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs
index c9ed3e19f1..590872979d 100644
--- a/libraries/base/Control/Concurrent/MVar.hs
+++ b/libraries/base/Control/Concurrent/MVar.hs
@@ -217,6 +217,8 @@ modifyMVar m io =
{-|
Like 'modifyMVar_', but the @IO@ action in the second argument is executed with
asynchronous exceptions masked.
+
+ /Since: 4.6.0.0/
-}
{-# INLINE modifyMVarMasked_ #-}
modifyMVarMasked_ :: MVar a -> (a -> IO a) -> IO ()
@@ -229,6 +231,8 @@ modifyMVarMasked_ m io =
{-|
Like 'modifyMVar', but the @IO@ action in the second argument is executed with
asynchronous exceptions masked.
+
+ /Since: 4.6.0.0/
-}
{-# INLINE modifyMVarMasked #-}
modifyMVarMasked :: MVar a -> (a -> IO (a,b)) -> IO b
@@ -245,6 +249,8 @@ addMVarFinalizer = GHC.MVar.addMVarFinalizer
-- | Make a 'Weak' pointer to an 'MVar', using the second argument as
-- a finalizer to run when 'MVar' is garbage-collected
+--
+-- /Since: 4.6.0.0/
mkWeakMVar :: MVar a -> IO () -> IO (Weak (MVar a))
mkWeakMVar m@(MVar m#) f = IO $ \s ->
case mkWeak# m# m f s of (# s1, w #) -> (# s1, Weak w #)
diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs
index 08ff6f9451..9eb024c456 100644
--- a/libraries/base/Data/Bits.hs
+++ b/libraries/base/Data/Bits.hs
@@ -269,6 +269,8 @@ class Bits b => FiniteBits b where
-- | Default implementation for 'bit'.
--
-- Note that: @bitDefault i = 1 `shiftL` i@
+--
+-- /Since: 4.6.0.0/
bitDefault :: (Bits a, Num a) => Int -> a
bitDefault = \i -> 1 `shiftL` i
{-# INLINE bitDefault #-}
@@ -276,6 +278,8 @@ bitDefault = \i -> 1 `shiftL` i
-- | Default implementation for 'testBit'.
--
-- Note that: @testBitDefault x i = (x .&. bit i) /= 0@
+--
+-- /Since: 4.6.0.0/
testBitDefault :: (Bits a, Num a) => a -> Int -> Bool
testBitDefault = \x i -> (x .&. bit i) /= 0
{-# INLINE testBitDefault #-}
@@ -284,6 +288,8 @@ testBitDefault = \x i -> (x .&. bit i) /= 0
--
-- This implementation is intentionally naive. Instances are expected to provide
-- an optimized implementation for their size.
+--
+-- /Since: 4.6.0.0/
popCountDefault :: (Bits a, Num a) => a -> Int
popCountDefault = go 0
where
diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs
index f4eb9ec143..1c1bb1b96b 100644
--- a/libraries/base/Data/IORef.hs
+++ b/libraries/base/Data/IORef.hs
@@ -70,6 +70,8 @@ modifyIORef :: IORef a -> (a -> a) -> IO ()
modifyIORef ref f = readIORef ref >>= writeIORef ref . f
-- |Strict version of 'modifyIORef'
+--
+-- /Since: 4.6.0.0/
modifyIORef' :: IORef a -> (a -> a) -> IO ()
modifyIORef' ref f = do
x <- readIORef ref
@@ -100,6 +102,8 @@ atomicModifyIORef = GHC.IORef.atomicModifyIORef
-- | Strict version of 'atomicModifyIORef'. This forces both the value stored
-- in the 'IORef' as well as the value returned.
+--
+-- /Since: 4.6.0.0/
atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b
atomicModifyIORef' ref f = do
b <- atomicModifyIORef ref
@@ -109,6 +113,8 @@ atomicModifyIORef' ref f = do
-- | Variant of 'writeIORef' with the \"barrier to reordering\" property that
-- 'atomicModifyIORef' has.
+--
+-- /Since: 4.6.0.0/
atomicWriteIORef :: IORef a -> a -> IO ()
atomicWriteIORef ref a = do
x <- atomicModifyIORef ref (\_ -> (a, ()))
diff --git a/libraries/base/Data/Ord.hs b/libraries/base/Data/Ord.hs
index 174855519e..f7d32f657b 100644
--- a/libraries/base/Data/Ord.hs
+++ b/libraries/base/Data/Ord.hs
@@ -40,6 +40,8 @@ comparing p x y = compare (p x) (p y)
-- values thus wrapped will give you the opposite of their normal sort order.
-- This is particularly useful when sorting in generalised list comprehensions,
-- as in: @then sortWith by 'Down' x@
+--
+-- /Since: 4.6.0.0/
newtype Down a = Down a deriving (Eq)
instance Ord a => Ord (Down a) where
diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs
index 486cc4b3de..dc65abc791 100644
--- a/libraries/base/Data/STRef.hs
+++ b/libraries/base/Data/STRef.hs
@@ -47,6 +47,8 @@ modifySTRef :: STRef s a -> (a -> a) -> ST s ()
modifySTRef ref f = writeSTRef ref . f =<< readSTRef ref
-- | Strict version of 'modifySTRef'
+--
+-- /Since: 4.6.0.0/
modifySTRef' :: STRef s a -> (a -> a) -> ST s ()
modifySTRef' ref f = do
x <- readSTRef ref
diff --git a/libraries/base/GHC/Conc/Sync.lhs b/libraries/base/GHC/Conc/Sync.lhs
index 3020b0745d..3461c7c4d4 100644
--- a/libraries/base/GHC/Conc/Sync.lhs
+++ b/libraries/base/GHC/Conc/Sync.lhs
@@ -507,6 +507,7 @@ threadCapability (ThreadId t) = IO $ \s ->
-- caller must use @deRefWeak@ first to determine whether the thread
-- still exists.
--
+-- /Since: 4.6.0.0/
mkWeakThreadId :: ThreadId -> IO (Weak ThreadId)
mkWeakThreadId t@(ThreadId t#) = IO $ \s ->
case mkWeakNoFinalizer# t# t s of
diff --git a/libraries/base/GHC/Exception.lhs b/libraries/base/GHC/Exception.lhs
index 7d40a94332..b878b6c05b 100644
--- a/libraries/base/GHC/Exception.lhs
+++ b/libraries/base/GHC/Exception.lhs
@@ -191,7 +191,7 @@ data ArithException
| LossOfPrecision
| DivideByZero
| Denormal
- | RatioZeroDenominator
+ | RatioZeroDenominator -- ^ /Since: 4.6.0.0/
deriving (Eq, Ord, Typeable)
divZeroException, overflowException, ratioZeroDenomException :: SomeException
diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index 6ab1e9e1a9..8937f53d5e 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -23,7 +23,8 @@
-- (<http://www.haskell.org/haskellwiki/GHC.Generics>)
-- or use the generic-deriving package on Hackage:
-- <http://hackage.haskell.org/package/generic-deriving>.
---
+--
+-- /Since: 4.6.0.0/
-----------------------------------------------------------------------------
module GHC.Generics (
diff --git a/libraries/base/GHC/IP.hs b/libraries/base/GHC/IP.hs
index 762f26bd85..4794c05452 100644
--- a/libraries/base/GHC/IP.hs
+++ b/libraries/base/GHC/IP.hs
@@ -3,6 +3,8 @@
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# OPTIONS_GHC -XNoImplicitPrelude #-}
+
+-- | /Since: 4.6.0.0/
module GHC.IP (IP(..)) where
import GHC.TypeLits
diff --git a/libraries/base/GHC/Stats.hsc b/libraries/base/GHC/Stats.hsc
index 024d1b22b6..5108dd3a29 100644
--- a/libraries/base/GHC/Stats.hsc
+++ b/libraries/base/GHC/Stats.hsc
@@ -28,6 +28,10 @@ import Foreign.Ptr
#include "Rts.h"
foreign import ccall "getGCStats" getGCStats_ :: Ptr () -> IO ()
+
+-- | Returns whether GC stats have been enabled (with @+RTS -T@, for example).
+--
+-- /Since: 4.6.0.0/
foreign import ccall "getGCStatsEnabled" getGCStatsEnabled :: IO Bool
-- I'm probably violating a bucket of constraints here... oops.
diff --git a/libraries/base/GHC/TypeLits.hs b/libraries/base/GHC/TypeLits.hs
index 0f32ae63d2..3f956460fe 100644
--- a/libraries/base/GHC/TypeLits.hs
+++ b/libraries/base/GHC/TypeLits.hs
@@ -14,7 +14,10 @@
{-# OPTIONS_GHC -XNoImplicitPrelude #-}
{-| This module is an internal GHC module. It declares the constants used
in the implementation of type-level natural numbers. The programmer interface
-for working with type-level naturals should be defined in a separate library. -}
+for working with type-level naturals should be defined in a separate library.
+
+/Since: 4.6.0.0/
+-}
module GHC.TypeLits
( -- * Kinds
diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs
index 4288a603c8..34eea8ca58 100644
--- a/libraries/base/System/Environment.hs
+++ b/libraries/base/System/Environment.hs
@@ -213,6 +213,8 @@ foreign import WINDOWS_CCONV unsafe "windows.h GetLastError"
-- there is no such value.
--
-- For POSIX users, this is equivalent to 'System.Posix.Env.getEnv'.
+--
+-- /Since: 4.6.0.0/
lookupEnv :: String -> IO (Maybe String)
#ifdef mingw32_HOST_OS
lookupEnv name = withCWString name $ \s -> try_size s 256
diff --git a/libraries/base/System/Environment/ExecutablePath.hsc b/libraries/base/System/Environment/ExecutablePath.hsc
index 10ef158e6c..4f863f2f8e 100644
--- a/libraries/base/System/Environment/ExecutablePath.hsc
+++ b/libraries/base/System/Environment/ExecutablePath.hsc
@@ -13,6 +13,7 @@
--
-- Function to retrieve the absolute filepath of the current executable.
--
+-- /Since: 4.6.0.0/
-----------------------------------------------------------------------------
module System.Environment.ExecutablePath ( getExecutablePath ) where
@@ -52,6 +53,8 @@ import System.Posix.Internals
--
-- Note that for scripts and interactive sessions, this is the path to
-- the interpreter (e.g. ghci.)
+--
+-- /Since: 4.6.0.0/
getExecutablePath :: IO FilePath
--------------------------------------------------------------------------------
diff --git a/libraries/base/Text/Read.hs b/libraries/base/Text/Read.hs
index b2c3d6bfc7..6c9d89db76 100644
--- a/libraries/base/Text/Read.hs
+++ b/libraries/base/Text/Read.hs
@@ -62,6 +62,8 @@ reads = readsPrec minPrec
-- | Parse a string using the 'Read' instance.
-- Succeeds if there is exactly one valid result.
-- A 'Left' value indicates a parse error.
+--
+-- /Since: 4.6.0.0/
readEither :: Read a => String -> Either String a
readEither s =
case [ x | (x,"") <- readPrec_to_S read' minPrec s ] of
@@ -76,6 +78,8 @@ readEither s =
-- | Parse a string using the 'Read' instance.
-- Succeeds if there is exactly one valid result.
+--
+-- /Since: 4.6.0.0/
readMaybe :: Read a => String -> Maybe a
readMaybe s = case readEither s of
Left _ -> Nothing
diff --git a/libraries/base/Text/Read/Lex.hs b/libraries/base/Text/Read/Lex.hs
index 28bad33852..f2ef4cc922 100644
--- a/libraries/base/Text/Read/Lex.hs
+++ b/libraries/base/Text/Read/Lex.hs
@@ -61,6 +61,7 @@ data Lexeme
| EOF
deriving (Eq, Show)
+-- | /Since: 4.6.0.0/
data Number = MkNumber Int -- Base
Digits -- Integral part
| MkDecimal Digits -- Integral part
@@ -130,6 +131,7 @@ numberToRangedRational (neg, pos) n@(MkDecimal iPart mFPart (Just exp))
else Just (numberToRational n)
numberToRangedRational _ n = Just (numberToRational n)
+-- | /Since: 4.6.0.0/
numberToRational :: Number -> Rational
numberToRational (MkNumber base iPart) = val (fromIntegral base) 0 iPart % 1
numberToRational (MkDecimal iPart mFPart mExp)