diff options
| author | Herbert Valerio Riedel <hvr@gnu.org> | 2014-12-16 12:07:10 +0100 | 
|---|---|---|
| committer | Herbert Valerio Riedel <hvr@gnu.org> | 2014-12-16 13:30:08 +0100 | 
| commit | 554aedab646075e12e53b44df04bcfbccbe03a73 (patch) | |
| tree | 0832201a44fd74632bbbd88fb77cb6c11eb34cf7 | |
| parent | 45a9696c550c5fe5e891b6d4710179272dc9f6db (diff) | |
| download | haskell-554aedab646075e12e53b44df04bcfbccbe03a73.tar.gz | |
Convert `/Since: .../` to new `@since ...` syntax
Starting with Haddock 2.16 there's a new built-in support for since-annotations
Note: This exposes a bug in the `@since` implementation (see e.g. `Data.Bits`)
69 files changed, 226 insertions, 226 deletions
| diff --git a/libraries/base/Control/Concurrent.hs b/libraries/base/Control/Concurrent.hs index 702d0bb3b4..35248bfba3 100644 --- a/libraries/base/Control/Concurrent.hs +++ b/libraries/base/Control/Concurrent.hs @@ -191,7 +191,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/ +-- @since 4.6.0.0  forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId  forkFinally action and_then =    mask $ \restore -> @@ -431,7 +431,7 @@ threadWaitWrite fd  -- is an IO action that can be used to deregister interest  -- in the file descriptor.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  threadWaitReadSTM :: Fd -> IO (STM (), IO ())  threadWaitReadSTM fd  #ifdef mingw32_HOST_OS @@ -455,7 +455,7 @@ threadWaitReadSTM fd  -- is an IO action that can be used to deregister interest  -- in the file descriptor.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  threadWaitWriteSTM :: Fd -> IO (STM (), IO ())  threadWaitWriteSTM fd  #ifdef mingw32_HOST_OS diff --git a/libraries/base/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs index 72a44d38d9..45c05fdc9b 100644 --- a/libraries/base/Control/Concurrent/MVar.hs +++ b/libraries/base/Control/Concurrent/MVar.hs @@ -193,7 +193,7 @@ withMVar m io =    Like 'withMVar', but the @IO@ action in the second argument is executed    with asynchronous exceptions masked. -  /Since: 4.7.0.0/ +  @since 4.7.0.0  -}  {-# INLINE withMVarMasked #-}  withMVarMasked :: MVar a -> (a -> IO b) -> IO b @@ -236,7 +236,7 @@ modifyMVar m io =    Like 'modifyMVar_', but the @IO@ action in the second argument is executed with    asynchronous exceptions masked. -  /Since: 4.6.0.0/ +  @since 4.6.0.0  -}  {-# INLINE modifyMVarMasked_ #-}  modifyMVarMasked_ :: MVar a -> (a -> IO a) -> IO () @@ -250,7 +250,7 @@ modifyMVarMasked_ m io =    Like 'modifyMVar', but the @IO@ action in the second argument is executed with    asynchronous exceptions masked. -  /Since: 4.6.0.0/ +  @since 4.6.0.0  -}  {-# INLINE modifyMVarMasked #-}  modifyMVarMasked :: MVar a -> (a -> IO (a,b)) -> IO b @@ -268,7 +268,7 @@ 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/ +-- @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/Control/Exception.hs b/libraries/base/Control/Exception.hs index 0bcbdca942..18c0e42914 100644 --- a/libraries/base/Control/Exception.hs +++ b/libraries/base/Control/Exception.hs @@ -219,7 +219,7 @@ A typical use of 'tryJust' for recovery looks like this:  -- When called outside 'mask', or inside 'uninterruptibleMask', this  -- function has no effect.  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  allowInterrupt :: IO ()  allowInterrupt = unsafeUnmask $ return () diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs index 07b011a6c3..6fa4a077d4 100644 --- a/libraries/base/Control/Monad.hs +++ b/libraries/base/Control/Monad.hs @@ -199,7 +199,7 @@ infixl 4 <$!>  -- | Strict version of 'Data.Functor.<$>'.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  (<$!>) :: Monad m => (a -> b) -> m a -> m b  {-# INLINE (<$!>) #-}  f <$!> m = do diff --git a/libraries/base/Data/Bifunctor.hs b/libraries/base/Data/Bifunctor.hs index 2e31ad5691..2412ce7d30 100644 --- a/libraries/base/Data/Bifunctor.hs +++ b/libraries/base/Data/Bifunctor.hs @@ -11,7 +11,7 @@  -- Stability   :  provisional  -- Portability :  portable  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  ----------------------------------------------------------------------------  module Data.Bifunctor    ( Bifunctor(..) @@ -51,7 +51,7 @@ import Control.Applicative  ( Const(..) )  -- 'second' (f '.' g) ≡ 'second' f '.' 'second' g  -- @  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  class Bifunctor p where      {-# MINIMAL bimap | first, second #-} diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index 69a0377f9b..84b1c031b1 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -156,7 +156,7 @@ class Eq a => Bits a where      -- implementation (which ought to be equivalent to 'zeroBits' for      -- types which possess a 0th bit).      -- -    -- /Since: 4.7.0.0/ +    -- @since 4.7.0.0      zeroBits :: a      zeroBits = clearBit (bit 0) 0 @@ -187,7 +187,7 @@ class Eq a => Bits a where          value of the argument is ignored.  Returns Nothing          for types that do not have a fixed bitsize, like 'Integer'. -        /Since: 4.7.0.0/ +        @since 4.7.0.0          -}      bitSizeMaybe      :: a -> Maybe Int @@ -224,7 +224,7 @@ class Eq a => Bits a where          Defaults to 'shiftL' unless defined explicitly by an instance. -        /Since: 4.5.0.0/ -} +        @since 4.5.0.0 -}      unsafeShiftL            :: a -> Int -> a      {-# INLINE unsafeShiftL #-}      x `unsafeShiftL` i = x `shiftL` i @@ -253,7 +253,7 @@ class Eq a => Bits a where          Defaults to 'shiftR' unless defined explicitly by an instance. -        /Since: 4.5.0.0/ -} +        @since 4.5.0.0 -}      unsafeShiftR            :: a -> Int -> a      {-# INLINE unsafeShiftR #-}      x `unsafeShiftR` i = x `shiftR` i @@ -284,12 +284,12 @@ class Eq a => Bits a where          Can be implemented using `popCountDefault' if @a@ is also an          instance of 'Num'. -        /Since: 4.5.0.0/ -} +        @since 4.5.0.0 -}      popCount          :: a -> Int  -- |The 'FiniteBits' class denotes types with a finite, fixed number of bits.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  class Bits b => FiniteBits b where      -- | Return the number of bits in the type of the argument.      -- The actual value of the argument is ignored. Moreover, 'finiteBitSize' @@ -300,7 +300,7 @@ class Bits b => FiniteBits b where      -- 'bitSizeMaybe' = 'Just' . 'finiteBitSize'      -- @      -- -    -- /Since: 4.7.0.0/ +    -- @since 4.7.0.0      finiteBitSize :: b -> Int      -- | Count number of zero bits preceding the most significant set bit. @@ -320,7 +320,7 @@ class Bits b => FiniteBits b where      -- integral types are implemented using CPU specific machine      -- instructions.      -- -    -- /Since: 4.8.0.0/ +    -- @since 4.8.0.0      countLeadingZeros :: b -> Int      countLeadingZeros x = (w-1) - go (w-1)        where @@ -350,7 +350,7 @@ class Bits b => FiniteBits b where      -- integral types are implemented using CPU specific machine      -- instructions.      -- -    -- /Since: 4.8.0.0/ +    -- @since 4.8.0.0      countTrailingZeros :: b -> Int      countTrailingZeros x = go 0        where @@ -369,7 +369,7 @@ class Bits b => FiniteBits b where  --  -- Note that: @bitDefault i = 1 `shiftL` i@  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  bitDefault :: (Bits a, Num a) => Int -> a  bitDefault = \i -> 1 `shiftL` i  {-# INLINE bitDefault #-} @@ -378,7 +378,7 @@ bitDefault = \i -> 1 `shiftL` i  --  -- Note that: @testBitDefault x i = (x .&. bit i) /= 0@  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  testBitDefault ::  (Bits a, Num a) => a -> Int -> Bool  testBitDefault = \x i -> (x .&. bit i) /= 0  {-# INLINE testBitDefault #-} @@ -388,7 +388,7 @@ 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/ +-- @since 4.6.0.0  popCountDefault :: (Bits a, Num a) => a -> Int  popCountDefault = go 0   where @@ -397,7 +397,7 @@ popCountDefault = go 0  {-# INLINABLE popCountDefault #-} --- Interpret 'Bool' as 1-bit bit-field; /Since: 4.7.0.0/ +-- Interpret 'Bool' as 1-bit bit-field; @since 4.7.0.0  instance Bits Bool where      (.&.) = (&&) @@ -557,7 +557,7 @@ instance Bits Integer where  -- 'fromIntegral', which is itself optimized with rules for @base@ types but may  -- go through 'Integer' for some type pairs.)  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b  toIntegralSized x                 -- See Note [toIntegralSized optimization] diff --git a/libraries/base/Data/Bool.hs b/libraries/base/Data/Bool.hs index 9f1bef6e7c..3e812d41b4 100644 --- a/libraries/base/Data/Bool.hs +++ b/libraries/base/Data/Bool.hs @@ -35,7 +35,7 @@ import GHC.Base  -- think of it as an if-then-else construct with its arguments  -- reordered.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  --  -- ==== __Examples__  -- diff --git a/libraries/base/Data/Coerce.hs b/libraries/base/Data/Coerce.hs index 653a857da8..23c37967df 100644 --- a/libraries/base/Data/Coerce.hs +++ b/libraries/base/Data/Coerce.hs @@ -16,7 +16,7 @@  -- More in-depth information can be found on the  -- <https://ghc.haskell.org/trac/ghc/wiki/Roles Roles wiki page>  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  -----------------------------------------------------------------------------  module Data.Coerce diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs index 901c9fd800..99bc0d466a 100644 --- a/libraries/base/Data/Either.hs +++ b/libraries/base/Data/Either.hs @@ -218,7 +218,7 @@ partitionEithers = foldr (either left right) ([],[])  -- | Return `True` if the given value is a `Left`-value, `False` otherwise.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  --  -- ==== __Examples__  -- @@ -250,7 +250,7 @@ isLeft (Right _) = False  -- | Return `True` if the given value is a `Right`-value, `False` otherwise.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  --  -- ==== __Examples__  -- diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs index f12a0e496d..d67a5dc61e 100644 --- a/libraries/base/Data/Fixed.hs +++ b/libraries/base/Data/Fixed.hs @@ -58,7 +58,7 @@ mod' n d = n - (fromInteger f) * d where      f = div' n d  -- | The type parameter should be an instance of 'HasResolution'. -newtype Fixed a = MkFixed Integer -- ^ /Since: 4.7.0.0/ +newtype Fixed a = MkFixed Integer -- ^ @since 4.7.0.0          deriving (Eq,Ord)  -- We do this because the automatically derived Data instance requires (Data a) context. diff --git a/libraries/base/Data/Function.hs b/libraries/base/Data/Function.hs index 1481147f0b..c5ded4cda5 100644 --- a/libraries/base/Data/Function.hs +++ b/libraries/base/Data/Function.hs @@ -95,6 +95,6 @@ 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 '$'.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  (&) :: a -> (a -> b) -> b  x & f = f x diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index c12564f23c..72ee9653e1 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -67,7 +67,7 @@ infixl 4 $>  -- | Flipped version of '<$'.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  --  -- ==== __Examples__  -- diff --git a/libraries/base/Data/Functor/Identity.hs b/libraries/base/Data/Functor/Identity.hs index 28ede2cd45..2465a1ee7d 100644 --- a/libraries/base/Data/Functor/Identity.hs +++ b/libraries/base/Data/Functor/Identity.hs @@ -25,7 +25,7 @@  --   applying the transformer to 'Identity'.  For example, @State s@  --   is an abbreviation for @StateT s 'Identity'@.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  -----------------------------------------------------------------------------  module Data.Functor.Identity ( @@ -38,7 +38,7 @@ import Data.Foldable  -- | Identity functor and monad. (a non-strict monad)  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  newtype Identity a = Identity { runIdentity :: a }      deriving (Eq, Ord, Traversable) diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs index 2981805cb6..ff6a8e62d6 100644 --- a/libraries/base/Data/IORef.hs +++ b/libraries/base/Data/IORef.hs @@ -71,7 +71,7 @@ modifyIORef ref f = readIORef ref >>= writeIORef ref . f  -- |Strict version of 'modifyIORef'  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  modifyIORef' :: IORef a -> (a -> a) -> IO ()  modifyIORef' ref f = do      x <- readIORef ref @@ -103,7 +103,7 @@ 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/ +-- @since 4.6.0.0  atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b  atomicModifyIORef' ref f = do      b <- atomicModifyIORef ref $ \a -> @@ -114,7 +114,7 @@ atomicModifyIORef' ref f = do  -- | Variant of 'writeIORef' with the \"barrier to reordering\" property that  -- 'atomicModifyIORef' has.  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  atomicWriteIORef :: IORef a -> a -> IO ()  atomicWriteIORef ref a = do      x <- atomicModifyIORef ref (\_ -> (a, ())) diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs index c3fb7e9ec7..ab85cf4c72 100644 --- a/libraries/base/Data/List.hs +++ b/libraries/base/Data/List.hs @@ -224,7 +224,7 @@ import GHC.Base ( Bool(..), Eq((==)), otherwise )  --  -- @'isSubsequenceOf' x y@ is equivalent to @'elem' x ('subsequences' y)@.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  --  -- ==== __Examples__  -- diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs index 288d71db34..dbabaff981 100644 --- a/libraries/base/Data/Monoid.hs +++ b/libraries/base/Data/Monoid.hs @@ -60,7 +60,7 @@ infixr 6 <>  -- | An infix synonym for 'mappend'.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  (<>) :: Monoid m => m -> m -> m  (<>) = mappend  {-# INLINE (<>) #-} @@ -177,7 +177,7 @@ instance Monoid (Last a) where  -- | Monoid under '<|>'.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  newtype Alt f a = Alt {getAlt :: f a}    deriving (Generic, Generic1, Read, Show, Eq, Ord, Num, Enum,              Monad, MonadPlus, Applicative, Alternative, Functor) diff --git a/libraries/base/Data/OldList.hs b/libraries/base/Data/OldList.hs index eb9f1ccedf..137ce42150 100644 --- a/libraries/base/Data/OldList.hs +++ b/libraries/base/Data/OldList.hs @@ -231,7 +231,7 @@ infix 5 \\ -- comment to fool cpp: https://www.haskell.org/ghc/docs/latest/html/  -- > dropWhileEnd isSpace "foo bar" == "foo bar"  -- > dropWhileEnd isSpace ("foo\n" ++ undefined) == "foo" ++ undefined  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  dropWhileEnd :: (a -> Bool) -> [a] -> [a]  dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) [] @@ -974,7 +974,7 @@ rqpart cmp x (y:ys) rle rgt r =  -- input list.  This is called the decorate-sort-undecorate paradigm, or  -- Schwartzian transform.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  sortOn :: Ord b => (a -> b) -> [a] -> [a]  sortOn f =    map snd . sortBy (comparing fst) . map (\x -> let y = f x in y `seq` (y, x)) diff --git a/libraries/base/Data/Ord.hs b/libraries/base/Data/Ord.hs index 624dae1e9a..809f148070 100644 --- a/libraries/base/Data/Ord.hs +++ b/libraries/base/Data/Ord.hs @@ -45,7 +45,7 @@ comparing p x y = compare (p x) (p y)  --  -- Provides 'Show' and 'Read' instances (/since: 4.7.0.0/).  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  newtype Down a = Down a deriving (Eq, Show, Read)  instance Ord a => Ord (Down a) where diff --git a/libraries/base/Data/Proxy.hs b/libraries/base/Data/Proxy.hs index 6ea20bb7e7..a9146214c0 100644 --- a/libraries/base/Data/Proxy.hs +++ b/libraries/base/Data/Proxy.hs @@ -13,7 +13,7 @@  --  -- Definition of a Proxy type (poly-kinded in GHC)  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  -----------------------------------------------------------------------------  module Data.Proxy diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs index 8df34bba95..60bccf50cb 100644 --- a/libraries/base/Data/STRef.hs +++ b/libraries/base/Data/STRef.hs @@ -46,7 +46,7 @@ modifySTRef ref f = writeSTRef ref . f =<< readSTRef ref  -- | Strict version of 'modifySTRef'  -- --- /Since: 4.6.0.0/ +-- @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/Data/Type/Bool.hs b/libraries/base/Data/Type/Bool.hs index 320d6a064e..137e266501 100644 --- a/libraries/base/Data/Type/Bool.hs +++ b/libraries/base/Data/Type/Bool.hs @@ -13,7 +13,7 @@  --  -- Basic operations on type-level Booleans.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  -----------------------------------------------------------------------------  module Data.Type.Bool ( diff --git a/libraries/base/Data/Type/Coercion.hs b/libraries/base/Data/Type/Coercion.hs index 7044339a3a..f9f64c1439 100644 --- a/libraries/base/Data/Type/Coercion.hs +++ b/libraries/base/Data/Type/Coercion.hs @@ -19,7 +19,7 @@  --  -- Definition of representational equality ('Coercion').  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  -----------------------------------------------------------------------------  module Data.Type.Coercion @@ -44,7 +44,7 @@ import GHC.Base  -- To use this equality in practice, pattern-match on the @Coercion a b@ to get out  -- the @Coercible a b@ instance, and then use 'coerce' to apply it.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  data Coercion a b where    Coercion :: Coercible a b => Coercion a b diff --git a/libraries/base/Data/Type/Equality.hs b/libraries/base/Data/Type/Equality.hs index 2fc327ecdb..59d4ea3455 100644 --- a/libraries/base/Data/Type/Equality.hs +++ b/libraries/base/Data/Type/Equality.hs @@ -23,7 +23,7 @@  -- Definition of propositional equality @(:~:)@. Pattern-matching on a variable  -- of type @(a :~: b)@ produces a proof that @a ~ b@.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  ----------------------------------------------------------------------------- @@ -56,7 +56,7 @@ infix 4 :~:  -- in practice, pattern-match on the @a :~: b@ to get out the @Refl@ constructor;  -- in the body of the pattern-match, the compiler knows that @a ~ b@.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  data a :~: b where    Refl :: a :~: a diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 4cbd8fe054..168600f732 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -104,7 +104,7 @@ cast x = if typeRep (Proxy :: Proxy a) == typeRep (Proxy :: Proxy b)  -- | Extract a witness of equality of two types  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  eqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~: b)  eqT = if typeRep (Proxy :: Proxy a) == typeRep (Proxy :: Proxy b)        then Just $ unsafeCoerce Refl diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index ccdd059c52..647697a57a 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -94,9 +94,9 @@ instance Ord TypeRep where  -- be built using 'mkTyCon'.  data TyCon = TyCon {     tyConHash    :: {-# UNPACK #-} !Fingerprint, -   tyConPackage :: String, -- ^ /Since: 4.5.0.0/ -   tyConModule  :: String, -- ^ /Since: 4.5.0.0/ -   tyConName    :: String  -- ^ /Since: 4.5.0.0/ +   tyConPackage :: String, -- ^ @since 4.5.0.0 +   tyConModule  :: String, -- ^ @since 4.5.0.0 +   tyConName    :: String  -- ^ @since 4.5.0.0   }  instance Eq TyCon where @@ -205,7 +205,7 @@ class Typeable a where  -- | Takes a value of type @a@ and returns a concrete representation  -- of that type.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  typeRep :: forall proxy a. Typeable a => proxy a -> TypeRep  typeRep _ = typeRep# (proxy# :: Proxy# a)  {-# INLINE typeRep #-} diff --git a/libraries/base/Data/Void.hs b/libraries/base/Data/Void.hs index a4f8778f58..6bcb1b36a7 100644 --- a/libraries/base/Data/Void.hs +++ b/libraries/base/Data/Void.hs @@ -17,7 +17,7 @@  -- A logically uninhabited data type, used to indicate that a given  -- term should not exist.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  ----------------------------------------------------------------------------  module Data.Void      ( Void @@ -32,7 +32,7 @@ import GHC.Generics  -- | Uninhabited data type  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  data Void deriving (Generic)  deriving instance Data Void @@ -62,13 +62,13 @@ instance Exception Void  -- | Since 'Void' values logically don't exist, this witnesses the  -- logical reasoning tool of \"ex falso quodlibet\".  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  absurd :: Void -> a  absurd a = case a of {}  -- | If 'Void' is uninhabited then any 'Functor' that holds only  -- values of type 'Void' is holding no values.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  vacuous :: Functor f => f Void -> f a  vacuous = fmap absurd diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs index 9b2911af16..389eb19d1b 100644 --- a/libraries/base/Debug/Trace.hs +++ b/libraries/base/Debug/Trace.hs @@ -69,7 +69,7 @@ import Data.List  -- | The 'traceIO' function outputs the trace message from the IO monad.  -- This sequences the output with respect to other IO actions.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  traceIO :: String -> IO ()  traceIO msg = do      withCString "%s\n" $ \cfmt -> do @@ -115,7 +115,7 @@ trace string expr = unsafePerformIO $ do  {-|  Like 'trace' but returns the message instead of a third value. -/Since: 4.7.0.0/ +@since 4.7.0.0  -}  traceId :: String -> String  traceId a = trace a a @@ -139,7 +139,7 @@ traceShow = trace . show  {-|  Like 'traceShow' but returns the shown value instead of a third value. -/Since: 4.7.0.0/ +@since 4.7.0.0  -}  traceShowId :: (Show a) => a -> a  traceShowId a = trace (show a) a @@ -155,7 +155,7 @@ monad, as 'traceIO' is in the 'IO' monad.  >   y <- ...  >   traceM $ "y: " ++ show y -/Since: 4.7.0.0/ +@since 4.7.0.0  -}  traceM :: (Monad m) => String -> m ()  traceM string = trace string $ return () @@ -169,7 +169,7 @@ Like 'traceM', but uses 'show' on the argument to convert it to a 'String'.  >   y <- ...  >   traceMShow $ x + y -/Since: 4.7.0.0/ +@since 4.7.0.0  -}  traceShowM :: (Show a, Monad m) => a -> m ()  traceShowM = traceM . show @@ -183,7 +183,7 @@ traceShowM = traceM . show  -- stack correspond to @SCC@ annotations, so it is a good idea to use  -- @-fprof-auto@ or @-fprof-auto-calls@ to add SCC annotations automatically.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  traceStack :: String -> a -> a  traceStack str expr = unsafePerformIO $ do     traceIO str @@ -216,7 +216,7 @@ traceStack str expr = unsafePerformIO $ do  -- duplicate events emitted if two CPUs simultaneously evaluate the same thunk  -- that uses 'traceEvent'.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  traceEvent :: String -> a -> a  traceEvent msg expr = unsafeDupablePerformIO $ do      traceEventIO msg @@ -228,7 +228,7 @@ traceEvent msg expr = unsafeDupablePerformIO $ do  -- Compared to 'traceEvent', 'traceEventIO' sequences the event with respect to  -- other IO actions.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  traceEventIO :: String -> IO ()  traceEventIO msg =    GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s -> @@ -266,7 +266,7 @@ traceEventIO msg =  -- duplicate events emitted if two CPUs simultaneously evaluate the same thunk  -- that uses 'traceMarker'.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  traceMarker :: String -> a -> a  traceMarker msg expr = unsafeDupablePerformIO $ do      traceMarkerIO msg @@ -278,7 +278,7 @@ traceMarker msg expr = unsafeDupablePerformIO $ do  -- Compared to 'traceMarker', 'traceMarkerIO' sequences the event with respect to  -- other IO actions.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  traceMarkerIO :: String -> IO ()  traceMarkerIO msg =    GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s -> diff --git a/libraries/base/Foreign/C/Error.hs b/libraries/base/Foreign/C/Error.hs index 347e58e759..761435183e 100644 --- a/libraries/base/Foreign/C/Error.hs +++ b/libraries/base/Foreign/C/Error.hs @@ -204,7 +204,7 @@ eNOTDIR         = Errno (CONST_ENOTDIR)  eNOTEMPTY       = Errno (CONST_ENOTEMPTY)  eNOTSOCK        = Errno (CONST_ENOTSOCK)  eNOTSUP         = Errno (CONST_ENOTSUP) --- ^ /Since: 4.7.0.0/ +-- ^ @since 4.7.0.0  eNOTTY          = Errno (CONST_ENOTTY)  eNXIO           = Errno (CONST_ENXIO)  eOPNOTSUPP      = Errno (CONST_EOPNOTSUPP) diff --git a/libraries/base/Foreign/C/Types.hs b/libraries/base/Foreign/C/Types.hs index e6ffaf0ce7..abaf5c73d6 100644 --- a/libraries/base/Foreign/C/Types.hs +++ b/libraries/base/Foreign/C/Types.hs @@ -184,11 +184,11 @@ ARITHMETIC_TYPE(CClock,HTYPE_CLOCK_T)  ARITHMETIC_TYPE(CTime,HTYPE_TIME_T)  -- | Haskell type representing the C @useconds_t@ type.  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  ARITHMETIC_TYPE(CUSeconds,HTYPE_USECONDS_T)  -- | Haskell type representing the C @suseconds_t@ type.  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  ARITHMETIC_TYPE(CSUSeconds,HTYPE_SUSECONDS_T)  -- FIXME: Implement and provide instances for Eq and Storable diff --git a/libraries/base/Foreign/Marshal/Utils.hs b/libraries/base/Foreign/Marshal/Utils.hs index c24c249a8d..6f2434610c 100644 --- a/libraries/base/Foreign/Marshal/Utils.hs +++ b/libraries/base/Foreign/Marshal/Utils.hs @@ -171,7 +171,7 @@ moveBytes dest src size  = do _ <- memmove dest src (fromIntegral size)  -- |Fill a given number of bytes in memory area with a byte value.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  fillBytes               :: Ptr a -> Word8 -> Int -> IO ()  fillBytes dest char size = do    _ <- memset dest (fromIntegral char) (fromIntegral size) diff --git a/libraries/base/GHC/Conc/Sync.hs b/libraries/base/GHC/Conc/Sync.hs index e1dc915c07..eb07137b76 100644 --- a/libraries/base/GHC/Conc/Sync.hs +++ b/libraries/base/GHC/Conc/Sync.hs @@ -193,7 +193,7 @@ instance Ord ThreadId where  --  -- Allocation accounting is accurate only to about 4Kbytes.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  setAllocationCounter :: Int64 -> IO ()  setAllocationCounter i = do    ThreadId t <- myThreadId @@ -202,7 +202,7 @@ setAllocationCounter i = do  -- | Return the current value of the allocation counter for the  -- current thread.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  getAllocationCounter :: IO Int64  getAllocationCounter = do    ThreadId t <- myThreadId @@ -227,7 +227,7 @@ getAllocationCounter = do  -- Compared to using timeouts, allocation limits don't count time  -- spent blocked or in foreign calls.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  enableAllocationLimit :: IO ()  enableAllocationLimit = do    ThreadId t <- myThreadId @@ -235,7 +235,7 @@ enableAllocationLimit = do  -- | Disable allocation limit processing for the current thread.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  disableAllocationLimit :: IO ()  disableAllocationLimit = do    ThreadId t <- myThreadId @@ -296,7 +296,7 @@ forkIO action = IO $ \ s ->  -- only be used in that thread; the behaviour is undefined if it is  -- invoked in a different thread.  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  forkIOWithUnmask :: ((forall a . IO a -> IO a) -> IO ()) -> IO ThreadId  forkIOWithUnmask io = forkIO (io unsafeUnmask) @@ -321,7 +321,7 @@ system supports that, although in practice this is usually unnecessary  (and may actually degrade performance in some cases - experimentation  is recommended). -/Since: 4.4.0.0/ +@since 4.4.0.0  -}  forkOn :: Int -> IO () -> IO ThreadId  forkOn (I# cpu) action = IO $ \ s -> @@ -332,7 +332,7 @@ forkOn (I# cpu) action = IO $ \ s ->  -- | Like 'forkIOWithUnmask', but the child thread is pinned to the  -- given CPU, as with 'forkOn'.  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  forkOnWithUnmask :: Int -> ((forall a . IO a -> IO a) -> IO ()) -> IO ThreadId  forkOnWithUnmask cpu io = forkOn cpu (io unsafeUnmask) @@ -352,7 +352,7 @@ Returns the number of Haskell threads that can run truly  simultaneously (on separate physical processors) at any given time.  To change  this value, use 'setNumCapabilities'. -/Since: 4.4.0.0/ +@since 4.4.0.0  -}  getNumCapabilities :: IO Int  getNumCapabilities = do @@ -371,7 +371,7 @@ capabilities is not set larger than the number of physical processor  cores, and it may often be beneficial to leave one or more cores free  to avoid contention with other processes in the machine. -/Since: 4.5.0.0/ +@since 4.5.0.0  -}  setNumCapabilities :: Int -> IO ()  setNumCapabilities i = c_setNumCapabilities (fromIntegral i) @@ -381,7 +381,7 @@ foreign import ccall safe "setNumCapabilities"  -- | Returns the number of CPUs that the machine has  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  getNumProcessors :: IO Int  getNumProcessors = fmap fromIntegral c_getNumberOfProcessors @@ -585,7 +585,7 @@ threadStatus (ThreadId t) = IO $ \s ->  -- that capability or not.  A thread is locked to a capability if it  -- was created with @forkOn@.  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  threadCapability :: ThreadId -> IO (Int, Bool)  threadCapability (ThreadId t) = IO $ \s ->     case threadStatus# t s of @@ -606,7 +606,7 @@ threadCapability (ThreadId t) = IO $ \s ->  -- caller must use @deRefWeak@ first to determine whether the thread  -- still exists.  -- --- /Since: 4.6.0.0/ +-- @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.hs b/libraries/base/GHC/Exception.hs index e2b7149dda..b77d50a628 100644 --- a/libraries/base/GHC/Exception.hs +++ b/libraries/base/GHC/Exception.hs @@ -144,7 +144,7 @@ class (Typeable e, Show e) => Exception e where      --      -- Default implementation: @'show'@.      -- -    -- /Since: 4.8.0.0/ +    -- @since 4.8.0.0      displayException :: e -> String      displayException = show @@ -178,7 +178,7 @@ data ArithException    | LossOfPrecision    | DivideByZero    | Denormal -  | RatioZeroDenominator -- ^ /Since: 4.6.0.0/ +  | RatioZeroDenominator -- ^ @since 4.6.0.0    deriving (Eq, Ord, Typeable)  divZeroException, overflowException, ratioZeroDenomException  :: SomeException diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs index d9e19f046e..93de419eb6 100755 --- a/libraries/base/GHC/Exts.hs +++ b/libraries/base/GHC/Exts.hs @@ -50,7 +50,7 @@ module GHC.Exts          --          -- | These are available from the /Trustworthy/ module "Data.Coerce" as well          -- -        -- /Since: 4.7.0.0/ +        -- @since 4.7.0.0          Data.Coerce.coerce, Data.Coerce.Coercible,          -- * Transform comprehensions @@ -151,7 +151,7 @@ data SpecConstrAnnotation = NoSpecConstr | ForceSpecConstr  -- | The 'IsList' class and its methods are intended to be used in  --   conjunction with the OverloadedLists extension.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  class IsList l where    -- | The 'Item' type function returns the type of items of the structure    --   @l@. diff --git a/libraries/base/GHC/Fingerprint.hs b/libraries/base/GHC/Fingerprint.hs index ba890004fa..8a92cd0595 100644 --- a/libraries/base/GHC/Fingerprint.hs +++ b/libraries/base/GHC/Fingerprint.hs @@ -72,7 +72,7 @@ fingerprintString str = unsafeDupablePerformIO $  -- | Computes the hash of a given file.  -- This function loops over the handle, running in constant memory.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  getFileHash :: FilePath -> IO Fingerprint  getFileHash path = withBinaryFile path ReadMode $ \h -> do    allocaBytes SIZEOF_STRUCT_MD5CONTEXT $ \pctxt -> do diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs index 8835df45e8..b89d628526 100644 --- a/libraries/base/GHC/Generics.hs +++ b/libraries/base/GHC/Generics.hs @@ -18,7 +18,7 @@  -- Stability   :  internal  -- Portability :  non-portable  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  --  -- If you're using @GHC.Generics@, you should consider using the  -- <http://hackage.haskell.org/package/generic-deriving> package, which diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs index 62c4975c37..e9ac94103d 100644 --- a/libraries/base/GHC/IO.hs +++ b/libraries/base/GHC/IO.hs @@ -174,7 +174,7 @@ of the duplicated IO actions is only run partially, and then interrupted  in the middle without an exception being raised. Therefore, functions  like 'bracket' cannot be used safely within 'unsafeDupablePerformIO'. -/Since: 4.4.0.0/ +@since 4.4.0.0  -}  {-# NOINLINE unsafeDupablePerformIO #-}      -- See Note [unsafeDupablePerformIO is NOINLINE] diff --git a/libraries/base/GHC/IO/Encoding.hs b/libraries/base/GHC/IO/Encoding.hs index 68bc0cfa4e..31683b4e68 100644 --- a/libraries/base/GHC/IO/Encoding.hs +++ b/libraries/base/GHC/IO/Encoding.hs @@ -103,7 +103,7 @@ utf32be = UTF32.utf32be  -- | The Unicode encoding of the current locale  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  getLocaleEncoding :: IO TextEncoding  -- | The Unicode encoding of the current locale, but allowing arbitrary @@ -116,17 +116,17 @@ getLocaleEncoding :: IO TextEncoding  -- the use of code pages is deprecated: Strings should be retrieved  -- via the "wide" W-family of UTF-16 APIs instead  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  getFileSystemEncoding :: IO TextEncoding  -- | The Unicode encoding of the current locale, but where undecodable  -- bytes are replaced with their closest visual match. Used for  -- the 'CString' marshalling functions in "Foreign.C.String"  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  getForeignEncoding :: IO TextEncoding --- | /Since: 4.5.0.0/ +-- | @since 4.5.0.0  setLocaleEncoding, setFileSystemEncoding, setForeignEncoding :: TextEncoding -> IO ()  (getLocaleEncoding, setLocaleEncoding)         = mkGlobal initLocaleEncoding @@ -138,7 +138,7 @@ mkGlobal x = unsafePerformIO $ do      x_ref <- newIORef x      return (readIORef x_ref, writeIORef x_ref) --- | /Since: 4.5.0.0/ +-- | @since 4.5.0.0  initLocaleEncoding, initFileSystemEncoding, initForeignEncoding :: TextEncoding  #if !defined(mingw32_HOST_OS) @@ -169,7 +169,7 @@ initForeignEncoding    = CodePage.mkLocaleEncoding IgnoreCodingFailure  -- discards information, so encode followed by decode is not the  -- identity.  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  char8 :: TextEncoding  char8 = Latin1.latin1 diff --git a/libraries/base/GHC/IO/Encoding/Latin1.hs b/libraries/base/GHC/IO/Encoding/Latin1.hs index 5ec7110973..34a4fca193 100644 --- a/libraries/base/GHC/IO/Encoding/Latin1.hs +++ b/libraries/base/GHC/IO/Encoding/Latin1.hs @@ -45,7 +45,7 @@ import GHC.IO.Encoding.Types  latin1 :: TextEncoding  latin1 = mkLatin1 ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkLatin1 :: CodingFailureMode -> TextEncoding  mkLatin1 cfm = TextEncoding { textEncodingName = "ISO8859-1",                                mkTextDecoder = latin1_DF cfm, @@ -74,7 +74,7 @@ latin1_EF cfm =  latin1_checked :: TextEncoding  latin1_checked = mkLatin1_checked ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkLatin1_checked :: CodingFailureMode -> TextEncoding  mkLatin1_checked cfm = TextEncoding { textEncodingName = "ISO8859-1(checked)",                                        mkTextDecoder = latin1_DF cfm, diff --git a/libraries/base/GHC/IO/Encoding/Types.hs b/libraries/base/GHC/IO/Encoding/Types.hs index 95bb2905a4..02a0d13e8b 100644 --- a/libraries/base/GHC/IO/Encoding/Types.hs +++ b/libraries/base/GHC/IO/Encoding/Types.hs @@ -67,7 +67,7 @@ data BufferCodec from to state = BufferCodec {     -- Currently, some implementations of @recover@ may mutate the input buffer.     -- In particular, this feature is used to implement transliteration.     -- -   -- /Since: 4.4.0.0/ +   -- @since 4.4.0.0    close  :: IO (),     -- ^ Resources associated with the encoding may now be released. @@ -121,7 +121,7 @@ instance Show TextEncoding where    -- | Returns the value of 'textEncodingName'    show te = textEncodingName te --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  data CodingProgress = InputUnderflow  -- ^ Stopped because the input contains insufficient available elements,                                        -- or all of the input sequence has been sucessfully translated.                      | OutputUnderflow -- ^ Stopped because the output contains insufficient free elements diff --git a/libraries/base/GHC/IO/Encoding/UTF16.hs b/libraries/base/GHC/IO/Encoding/UTF16.hs index 4dd393b418..192f30beb9 100644 --- a/libraries/base/GHC/IO/Encoding/UTF16.hs +++ b/libraries/base/GHC/IO/Encoding/UTF16.hs @@ -55,7 +55,7 @@ import GHC.IORef  utf16  :: TextEncoding  utf16 = mkUTF16 ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkUTF16 :: CodingFailureMode -> TextEncoding  mkUTF16 cfm =  TextEncoding { textEncodingName = "UTF-16",                                mkTextDecoder = utf16_DF cfm, @@ -141,7 +141,7 @@ bom2 = bomL  utf16be :: TextEncoding  utf16be = mkUTF16be ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkUTF16be :: CodingFailureMode -> TextEncoding  mkUTF16be cfm = TextEncoding { textEncodingName = "UTF-16BE",                                 mkTextDecoder = utf16be_DF cfm, @@ -170,7 +170,7 @@ utf16be_EF cfm =  utf16le :: TextEncoding  utf16le = mkUTF16le ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkUTF16le :: CodingFailureMode -> TextEncoding  mkUTF16le cfm = TextEncoding { textEncodingName = "UTF16-LE",                                 mkTextDecoder = utf16le_DF cfm, diff --git a/libraries/base/GHC/IO/Encoding/UTF32.hs b/libraries/base/GHC/IO/Encoding/UTF32.hs index c874224682..26b5e448ca 100644 --- a/libraries/base/GHC/IO/Encoding/UTF32.hs +++ b/libraries/base/GHC/IO/Encoding/UTF32.hs @@ -55,7 +55,7 @@ import GHC.IORef  utf32  :: TextEncoding  utf32 = mkUTF32 ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkUTF32 :: CodingFailureMode -> TextEncoding  mkUTF32 cfm = TextEncoding { textEncodingName = "UTF-32",                               mkTextDecoder = utf32_DF cfm, @@ -144,7 +144,7 @@ utf32_native_encode = utf32be_encode  utf32be :: TextEncoding  utf32be = mkUTF32be ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkUTF32be :: CodingFailureMode -> TextEncoding  mkUTF32be cfm = TextEncoding { textEncodingName = "UTF-32BE",                                 mkTextDecoder = utf32be_DF cfm, @@ -174,7 +174,7 @@ utf32be_EF cfm =  utf32le :: TextEncoding  utf32le = mkUTF32le ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkUTF32le :: CodingFailureMode -> TextEncoding  mkUTF32le cfm = TextEncoding { textEncodingName = "UTF-32LE",                                 mkTextDecoder = utf32le_DF cfm, diff --git a/libraries/base/GHC/IO/Encoding/UTF8.hs b/libraries/base/GHC/IO/Encoding/UTF8.hs index 1c48acf18e..18d034ad15 100644 --- a/libraries/base/GHC/IO/Encoding/UTF8.hs +++ b/libraries/base/GHC/IO/Encoding/UTF8.hs @@ -43,7 +43,7 @@ import Data.Bits  utf8 :: TextEncoding  utf8 = mkUTF8 ErrorOnCodingFailure --- | /Since: 4.4.0.0/ +-- | @since 4.4.0.0  mkUTF8 :: CodingFailureMode -> TextEncoding  mkUTF8 cfm = TextEncoding { textEncodingName = "UTF-8",                              mkTextDecoder = utf8_DF cfm, diff --git a/libraries/base/GHC/IO/Exception.hs b/libraries/base/GHC/IO/Exception.hs index f811e5a43e..6701fdf67a 100644 --- a/libraries/base/GHC/IO/Exception.hs +++ b/libraries/base/GHC/IO/Exception.hs @@ -103,7 +103,7 @@ instance Show Deadlock where  -- 'GHC.Conc.setAllocationCounter' and  -- 'GHC.Conc.enableAllocationLimit'.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  data AllocationLimitExceeded = AllocationLimitExceeded      deriving Typeable @@ -131,7 +131,7 @@ instance Show AssertionFailed where  -- |Superclass for asynchronous exceptions.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  data SomeAsyncException = forall e . Exception e => SomeAsyncException e    deriving Typeable @@ -140,11 +140,11 @@ instance Show SomeAsyncException where  instance Exception SomeAsyncException --- |/Since: 4.7.0.0/ +-- |@since 4.7.0.0  asyncExceptionToException :: Exception e => e -> SomeException  asyncExceptionToException = toException . SomeAsyncException --- |/Since: 4.7.0.0/ +-- |@since 4.7.0.0  asyncExceptionFromException :: Exception e => SomeException -> Maybe e  asyncExceptionFromException x = do      SomeAsyncException a <- fromException x diff --git a/libraries/base/GHC/IO/Handle/FD.hs b/libraries/base/GHC/IO/Handle/FD.hs index ac792de4fb..181aad7831 100644 --- a/libraries/base/GHC/IO/Handle/FD.hs +++ b/libraries/base/GHC/IO/Handle/FD.hs @@ -157,7 +157,7 @@ openFile fp im =  -- non-blocking mode then the open will fail if there are no writers,  -- whereas a blocking open will block until a writer appears.  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  openFileBlocking :: FilePath -> IOMode -> IO Handle  openFileBlocking fp im =    catchException diff --git a/libraries/base/GHC/IP.hs b/libraries/base/GHC/IP.hs index b80ee4b3fb..9a4a0ec009 100644 --- a/libraries/base/GHC/IP.hs +++ b/libraries/base/GHC/IP.hs @@ -5,7 +5,7 @@  {-# LANGUAGE DataKinds #-}  {-# LANGUAGE NoImplicitPrelude #-} --- | /Since: 4.6.0.0/ +-- | @since 4.6.0.0  module GHC.IP (IP(..)) where  import GHC.TypeLits diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs index 19c771bdab..34ba445826 100644 --- a/libraries/base/GHC/List.hs +++ b/libraries/base/GHC/List.hs @@ -67,7 +67,7 @@ badHead = errorEmptyList "head"  -- returns 'Nothing'. If the list is non-empty, returns @'Just' (x, xs)@,  -- where @x@ is the head of the list and @xs@ its tail.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  uncons                  :: [a] -> Maybe (a, [a])  uncons []               = Nothing  uncons (x:xs)           = Just (x, xs) diff --git a/libraries/base/GHC/MVar.hs b/libraries/base/GHC/MVar.hs index 0ba122b543..a5054cc8fe 100644 --- a/libraries/base/GHC/MVar.hs +++ b/libraries/base/GHC/MVar.hs @@ -156,7 +156,7 @@ tryPutMVar (MVar mvar#) x = IO $ \ s# ->  -- returns immediately, with 'Nothing' if the 'MVar' was empty, or  -- @'Just' a@ if the 'MVar' was full with contents @a@.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  tryReadMVar :: MVar a -> IO (Maybe a)  tryReadMVar (MVar m) = IO $ \ s ->      case tryReadMVar# m s of diff --git a/libraries/base/GHC/Natural.hs b/libraries/base/GHC/Natural.hs index 0211061a32..71e3498f2c 100644 --- a/libraries/base/GHC/Natural.hs +++ b/libraries/base/GHC/Natural.hs @@ -26,7 +26,7 @@  -- change.  It's recommended use the "Numeric.Natural" module to import  -- the 'Natural' type.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  -----------------------------------------------------------------------------  module GHC.Natural      ( -- * The 'Natural' number type @@ -81,7 +81,7 @@ default ()  -- Operations whose result would be negative  -- @'throw' ('Underflow' :: 'ArithException')@.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  data Natural = NatS#                 GmpLimb# -- ^ in @[0, maxBound::Word]@               | NatJ# {-# UNPACK #-} !BigNat   -- ^ in @]maxBound::Word, +inf[@                                                -- @@ -96,7 +96,7 @@ data Natural = NatS#                 GmpLimb# -- ^ in @[0, maxBound::Word]@  -- This operation is mostly useful for test-suites and/or code which  -- constructs 'Integer' values directly.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  isValidNatural :: Natural -> Bool  isValidNatural (NatS# _)  = True  isValidNatural (NatJ# bn) = isTrue# (isValidBigNat# bn) @@ -381,7 +381,7 @@ minusNatural (NatJ# x) (NatJ# y)  -- | 'Natural' subtraction. Returns 'Nothing's for non-positive results.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  minusNaturalMaybe :: Natural -> Natural -> Maybe Natural  minusNaturalMaybe x         (NatS# 0##) = Just x  minusNaturalMaybe (NatS# x) (NatS# y) = case subWordC# x y of @@ -439,7 +439,7 @@ naturalToInt (NatJ# bn) = I# (bigNatToInt bn)  -- Operations whose result would be negative  -- @'throw' ('Underflow' :: 'ArithException')@.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  newtype Natural = Natural Integer -- ^ __Invariant__: non-negative 'Integer'                  deriving (Eq,Ord,Ix) @@ -448,7 +448,7 @@ newtype Natural = Natural Integer -- ^ __Invariant__: non-negative 'Integer'  -- This operation is mostly useful for test-suites and/or code which  -- constructs 'Integer' values directly.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  isValidNatural :: Natural -> Bool  isValidNatural (Natural i) = i >= 0 @@ -479,7 +479,7 @@ instance Num Natural where  -- | 'Natural' subtraction. Returns 'Nothing's for non-positive results.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  minusNaturalMaybe :: Natural -> Natural -> Maybe Natural  minusNaturalMaybe x y    | x >= y    = Just (x - y) @@ -572,7 +572,7 @@ instance Integral Natural where  -- | Construct 'Natural' from 'Word' value.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  wordToNatural :: Word -> Natural  #if HAVE_GMP_BIGNAT  wordToNatural (W# w#) = NatS# w# @@ -583,7 +583,7 @@ wordToNatural w = Natural (fromIntegral w)  -- | Try downcasting 'Natural' to 'Word' value.  -- Returns 'Nothing' if value doesn't fit in 'Word'.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  naturalToWordMaybe :: Natural -> Maybe Word  #if HAVE_GMP_BIGNAT  naturalToWordMaybe (NatS# w#) = Just (W# w#) @@ -612,7 +612,7 @@ instance Data Natural where  -- | \"@'powModNatural' /b/ /e/ /m/@\" computes base @/b/@ raised to  -- exponent @/e/@ modulo @/m/@.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  powModNatural :: Natural -> Natural -> Natural -> Natural  #if HAVE_GMP_BIGNAT  powModNatural _           _           (NatS# 0##) = throw DivideByZero diff --git a/libraries/base/GHC/Profiling.hs b/libraries/base/GHC/Profiling.hs index 281d9b10d1..732917684d 100644 --- a/libraries/base/GHC/Profiling.hs +++ b/libraries/base/GHC/Profiling.hs @@ -1,7 +1,7 @@  {-# LANGUAGE Trustworthy #-}  {-# LANGUAGE NoImplicitPrelude #-} --- | /Since: 4.7.0.0/ +-- | @since 4.7.0.0  module GHC.Profiling where  import GHC.Base diff --git a/libraries/base/GHC/RTS/Flags.hsc b/libraries/base/GHC/RTS/Flags.hsc index 1d75568061..ff1bf694f1 100644 --- a/libraries/base/GHC/RTS/Flags.hsc +++ b/libraries/base/GHC/RTS/Flags.hsc @@ -6,7 +6,7 @@  -- <https://www.haskell.org/ghc/docs/latest/html/users_guide/runtime-control.html GHC User's Guide>,  -- or by running RTS help message using @+RTS --help@.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  --  module GHC.RTS.Flags    ( RTSFlags (..) diff --git a/libraries/base/GHC/Stack.hsc b/libraries/base/GHC/Stack.hsc index 611e5c9ba6..0aa4d1768d 100644 --- a/libraries/base/GHC/Stack.hsc +++ b/libraries/base/GHC/Stack.hsc @@ -12,7 +12,7 @@  --  -- Access to GHC's call-stack simulation  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  -----------------------------------------------------------------------------  {-# LANGUAGE UnboxedTuples, MagicHash, NoImplicitPrelude #-} @@ -87,7 +87,7 @@ ccSrcSpan p = (# peek CostCentre, srcloc) p  -- Otherwise, the list returned is likely to be empty or  -- uninformative.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  currentCallStack :: IO [String]  currentCallStack = ccsToStrings =<< getCurrentCCS () @@ -109,7 +109,7 @@ ccsToStrings ccs0 = go ccs0 []  -- | Get the stack trace attached to an object.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  whoCreated :: a -> IO [String]  whoCreated obj = do    ccs <- getCCSOf obj @@ -121,7 +121,7 @@ renderStack strs = "Stack trace:" ++ concatMap ("\n  "++) (reverse strs)  -- | Like the function 'error', but appends a stack trace to the error  -- message if one is available.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  errorWithStackTrace :: String -> a  errorWithStackTrace x = unsafeDupablePerformIO $ do     stack <- ccsToStrings =<< getCurrentCCS x diff --git a/libraries/base/GHC/Stats.hsc b/libraries/base/GHC/Stats.hsc index 226a0e1f88..7bcc221c5f 100644 --- a/libraries/base/GHC/Stats.hsc +++ b/libraries/base/GHC/Stats.hsc @@ -10,7 +10,7 @@  --  -- This module is GHC-only and should not be considered portable.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  -----------------------------------------------------------------------------  module GHC.Stats      ( GCStats(..) @@ -34,14 +34,14 @@ foreign import ccall "getGCStats"        getGCStats_       :: Ptr () -> IO ()  -- | Returns whether GC stats have been enabled (with @+RTS -T@, for example).  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  foreign import ccall "getGCStatsEnabled" getGCStatsEnabled :: IO Bool  -- I'm probably violating a bucket of constraints here... oops.  -- | Global garbage collection and memory statistics.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  data GCStats = GCStats      { bytesAllocated :: !Int64 -- ^ Total number of bytes allocated      , numGcs :: !Int64 -- ^ Number of garbage collections performed @@ -89,7 +89,7 @@ data GCStats = GCStats  -- garbage collection.  If you would like your statistics as recent as  -- possible, first run a 'System.Mem.performGC'.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  getGCStats :: IO GCStats  getGCStats = do    statsEnabled <- getGCStatsEnabled diff --git a/libraries/base/GHC/TypeLits.hs b/libraries/base/GHC/TypeLits.hs index 4dde7a3c28..6da103e73c 100644 --- a/libraries/base/GHC/TypeLits.hs +++ b/libraries/base/GHC/TypeLits.hs @@ -17,7 +17,7 @@  in the implementation of type-level natural numbers.  The programmer interface  for working with type-level naturals should be defined in a separate library. -/Since: 4.6.0.0/ +@since 4.6.0.0  -}  module GHC.TypeLits @@ -61,33 +61,33 @@ data Symbol  -- | This class gives the integer associated with a type-level natural.  -- There are instances of the class for every concrete literal: 0, 1, 2, etc.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  class KnownNat (n :: Nat) where    natSing :: SNat n  -- | This class gives the string associated with a type-level symbol.  -- There are instances of the class for every concrete literal: "hello", etc.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  class KnownSymbol (n :: Symbol) where    symbolSing :: SSymbol n --- | /Since: 4.7.0.0/ +-- | @since 4.7.0.0  natVal :: forall n proxy. KnownNat n => proxy n -> Integer  natVal _ = case natSing :: SNat n of               SNat x -> x --- | /Since: 4.7.0.0/ +-- | @since 4.7.0.0  symbolVal :: forall n proxy. KnownSymbol n => proxy n -> String  symbolVal _ = case symbolSing :: SSymbol n of                  SSymbol x -> x --- | /Since: 4.8.0.0/ +-- | @since 4.8.0.0  natVal' :: forall n. KnownNat n => Proxy# n -> Integer  natVal' _ = case natSing :: SNat n of               SNat x -> x --- | /Since: 4.8.0.0/ +-- | @since 4.8.0.0  symbolVal' :: forall n. KnownSymbol n => Proxy# n -> String  symbolVal' _ = case symbolSing :: SSymbol n of                  SSymbol x -> x @@ -96,15 +96,15 @@ symbolVal' _ = case symbolSing :: SSymbol n of  -- | This type represents unknown type-level natural numbers.  data SomeNat    = forall n. KnownNat n    => SomeNat    (Proxy n) -                  -- ^ /Since: 4.7.0.0/ +                  -- ^ @since 4.7.0.0  -- | This type represents unknown type-level symbols.  data SomeSymbol = forall n. KnownSymbol n => SomeSymbol (Proxy n) -                  -- ^ /Since: 4.7.0.0/ +                  -- ^ @since 4.7.0.0  -- | Convert an integer into an unknown type-level natural.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  someNatVal :: Integer -> Maybe SomeNat  someNatVal n    | n >= 0        = Just (withSNat SomeNat (SNat n) Proxy) @@ -112,7 +112,7 @@ someNatVal n  -- | Convert a string into an unknown type-level symbol.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  someSymbolVal :: String -> SomeSymbol  someSymbolVal n   = withSSymbol SomeSymbol (SSymbol n) Proxy @@ -168,12 +168,12 @@ type x <= y = (x <=? y) ~ 'True  -- | Comparison of type-level symbols, as a function.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  type family CmpSymbol (m :: Symbol) (n :: Symbol) :: Ordering  -- | Comparison of type-level naturals, as a function.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  type family CmpNat    (m :: Nat)    (n :: Nat)    :: Ordering  {- | Comparison of type-level naturals, as a function. @@ -193,7 +193,7 @@ type family (m :: Nat) ^ (n :: Nat) :: Nat  -- | Subtraction of type-level naturals.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  type family (m :: Nat) - (n :: Nat) :: Nat @@ -202,7 +202,7 @@ type family (m :: Nat) - (n :: Nat) :: Nat  -- | We either get evidence that this function was instantiated with the  -- same type-level numbers, or 'Nothing'.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  sameNat :: (KnownNat a, KnownNat b) =>             Proxy a -> Proxy b -> Maybe (a :~: b)  sameNat x y @@ -212,7 +212,7 @@ sameNat x y  -- | We either get evidence that this function was instantiated with the  -- same type-level symbols, or 'Nothing'.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  sameSymbol :: (KnownSymbol a, KnownSymbol b) =>                Proxy a -> Proxy b -> Maybe (a :~: b)  sameSymbol x y diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs index 5351c0b94d..6663f59b7d 100644 --- a/libraries/base/GHC/Word.hs +++ b/libraries/base/GHC/Word.hs @@ -306,7 +306,7 @@ instance FiniteBits Word16 where  -- | Swap bytes in 'Word16'.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  byteSwap16 :: Word16 -> Word16  byteSwap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#)) @@ -538,7 +538,7 @@ instance Read Word32 where  -- | Reverse order of bytes in 'Word32'.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  byteSwap32 :: Word32 -> Word32  byteSwap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#)) @@ -794,7 +794,7 @@ instance Read Word64 where  -- | Reverse order of bytes in 'Word64'.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  #if WORD_SIZE_IN_BITS < 64  byteSwap64 :: Word64 -> Word64  byteSwap64 (W64# w#) = W64# (byteSwap64# w#) diff --git a/libraries/base/Numeric.hs b/libraries/base/Numeric.hs index 7cba671309..4e24bfe7a8 100644 --- a/libraries/base/Numeric.hs +++ b/libraries/base/Numeric.hs @@ -187,7 +187,7 @@ showGFloat d x =  showString (formatRealFloat FFGeneric d x)  -- This behaves as 'showFFloat', except that a decimal point  -- is always guaranteed, even if not needed.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  showFFloatAlt    :: (RealFloat a) => Maybe Int -> a -> ShowS  -- | Show a signed 'RealFloat' value @@ -197,7 +197,7 @@ showFFloatAlt    :: (RealFloat a) => Maybe Int -> a -> ShowS  -- This behaves as 'showFFloat', except that a decimal point  -- is always guaranteed, even if not needed.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  showGFloatAlt    :: (RealFloat a) => Maybe Int -> a -> ShowS  showFFloatAlt d x =  showString (formatRealFloatAlt FFFixed d True x) diff --git a/libraries/base/Numeric/Natural.hs b/libraries/base/Numeric/Natural.hs index 3a96501f1e..78fa147a66 100644 --- a/libraries/base/Numeric/Natural.hs +++ b/libraries/base/Numeric/Natural.hs @@ -14,7 +14,7 @@  --  -- The arbitrary-precision 'Natural' number type.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  -----------------------------------------------------------------------------  module Numeric.Natural diff --git a/libraries/base/System/Environment.hs b/libraries/base/System/Environment.hs index 9beefc4be3..066329c4e7 100644 --- a/libraries/base/System/Environment.hs +++ b/libraries/base/System/Environment.hs @@ -212,7 +212,7 @@ foreign import WINDOWS_CCONV unsafe "windows.h GetLastError"  --  -- For POSIX users, this is equivalent to 'System.Posix.Env.getEnv'.  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  lookupEnv :: String -> IO (Maybe String)  #ifdef mingw32_HOST_OS  lookupEnv name = withCWString name $ \s -> try_size s 256 @@ -267,7 +267,7 @@ ioe_missingEnvVar name = ioException (IOError Nothing NoSuchThing "getEnv"  -- Throws `Control.Exception.IOException` if @name@ is the empty string or  -- contains an equals sign.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  setEnv :: String -> String -> IO ()  setEnv key_ value_    | null key       = throwIO (mkIOError InvalidArgument "setEnv" Nothing Nothing) @@ -311,7 +311,7 @@ foreign import ccall unsafe "putenv" c_putenv :: CString -> IO CInt  -- Throws `Control.Exception.IOException` if @name@ is the empty string or  -- contains an equals sign.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  unsetEnv :: String -> IO ()  #ifdef mingw32_HOST_OS  unsetEnv key = withCWString key $ \k -> do diff --git a/libraries/base/System/Environment/ExecutablePath.hsc b/libraries/base/System/Environment/ExecutablePath.hsc index 22665f419b..410e3acda2 100644 --- a/libraries/base/System/Environment/ExecutablePath.hsc +++ b/libraries/base/System/Environment/ExecutablePath.hsc @@ -13,7 +13,7 @@  --  -- Function to retrieve the absolute filepath of the current executable.  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  -----------------------------------------------------------------------------  module System.Environment.ExecutablePath ( getExecutablePath ) where @@ -54,7 +54,7 @@ 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/ +-- @since 4.6.0.0  getExecutablePath :: IO FilePath  -------------------------------------------------------------------------------- diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs index 088a76bd96..2d0e6928ae 100644 --- a/libraries/base/System/Exit.hs +++ b/libraries/base/System/Exit.hs @@ -77,6 +77,6 @@ exitSuccess = exitWith ExitSuccess  -- | Write given error message to `stderr` and terminate with `exitFailure`.  -- --- /Since: 4.8.0.0/ +-- @since 4.8.0.0  die :: String -> IO a  die err = hPutStrLn stderr err >> exitFailure diff --git a/libraries/base/System/IO/Error.hs b/libraries/base/System/IO/Error.hs index b281fd59eb..2de6629a89 100644 --- a/libraries/base/System/IO/Error.hs +++ b/libraries/base/System/IO/Error.hs @@ -98,7 +98,7 @@ import Text.Show  -- Non-I\/O exceptions are not caught by this variant; to catch all  -- exceptions, use 'Control.Exception.try' from "Control.Exception".  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  tryIOError     :: IO a -> IO (Either IOError a)  tryIOError f   =  catch (do r <- f                              return (Right r)) @@ -332,6 +332,6 @@ annotateIOError ioe loc hdl path =  -- Non-I\/O exceptions are not caught by this variant; to catch all  -- exceptions, use 'Control.Exception.catch' from "Control.Exception".  -- --- /Since: 4.4.0.0/ +-- @since 4.4.0.0  catchIOError :: IO a -> (IOError -> IO a) -> IO a  catchIOError = catch diff --git a/libraries/base/System/IO/Unsafe.hs b/libraries/base/System/IO/Unsafe.hs index 91ce45c62b..a28fb4be1b 100644 --- a/libraries/base/System/IO/Unsafe.hs +++ b/libraries/base/System/IO/Unsafe.hs @@ -40,7 +40,7 @@ import Control.Exception  -- In this case, the child thread will receive a @NonTermination@  -- exception instead of waiting for the value of @r@ to be computed.  -- --- /Since: 4.5.0.0/ +-- @since 4.5.0.0  unsafeFixIO :: (a -> IO a) -> IO a  unsafeFixIO k = do    ref <- newIORef (throw NonTermination) diff --git a/libraries/base/System/Mem.hs b/libraries/base/System/Mem.hs index 09dfdf9191..a894f4d343 100644 --- a/libraries/base/System/Mem.hs +++ b/libraries/base/System/Mem.hs @@ -26,10 +26,10 @@ performGC = performMajorGC  -- | Triggers an immediate garbage collection.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  foreign import ccall "performMajorGC" performMajorGC :: IO ()  -- | Triggers an immediate minor garbage collection.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  foreign import ccall "performGC" performMinorGC :: IO () diff --git a/libraries/base/System/Mem/StableName.hs b/libraries/base/System/Mem/StableName.hs index 9da42e516e..56f815cf33 100644 --- a/libraries/base/System/Mem/StableName.hs +++ b/libraries/base/System/Mem/StableName.hs @@ -115,7 +115,7 @@ instance Eq (StableName a) where  -- | Equality on 'StableName' that does not require that the types of  -- the arguments match.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  eqStableName :: StableName a -> StableName b -> Bool  eqStableName (StableName sn1) (StableName sn2) =         case eqStableName# sn1 sn2 of diff --git a/libraries/base/Text/Printf.hs b/libraries/base/Text/Printf.hs index 6c911daea7..cc8c462688 100644 --- a/libraries/base/Text/Printf.hs +++ b/libraries/base/Text/Printf.hs @@ -311,9 +311,9 @@ instance (PrintfArg a, HPrintfType r) => HPrintfType (a -> r) where  -- default 'parseFormat' expects no modifiers: this is the normal  -- case. Minimal instance: 'formatArg'.  class PrintfArg a where -    -- | /Since: 4.7.0.0/ +    -- | @since 4.7.0.0      formatArg :: a -> FieldFormatter -    -- | /Since: 4.7.0.0/ +    -- | @since 4.7.0.0      parseFormat :: a -> ModifierParser      parseFormat _ (c : cs) = FormatParse "" c cs      parseFormat _ "" = errorShortFormat @@ -384,9 +384,9 @@ instance PrintfArg Double where  -- type, is not allowable as a typeclass instance. 'IsChar'  -- is exported for backward-compatibility.  class IsChar c where -    -- | /Since: 4.7.0.0/ +    -- | @since 4.7.0.0      toChar :: c -> Char -    -- | /Since: 4.7.0.0/ +    -- | @since 4.7.0.0      fromChar :: Char -> c  instance IsChar Char where @@ -398,19 +398,19 @@ instance IsChar Char where  -- | Whether to left-adjust or zero-pad a field. These are  -- mutually exclusive, with 'LeftAdjust' taking precedence.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  data FormatAdjustment = LeftAdjust | ZeroPad  -- | How to handle the sign of a numeric field.  These are  -- mutually exclusive, with 'SignPlus' taking precedence.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  data FormatSign = SignPlus | SignSpace  -- | Description of field formatting for 'formatArg'. See UNIX `printf`(3)  -- for a description of how field formatting works.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  data FieldFormat = FieldFormat {    fmtWidth :: Maybe Int,       -- ^ Total width of the field.    fmtPrecision :: Maybe Int,   -- ^ Secondary field width specifier. @@ -444,7 +444,7 @@ data FieldFormat = FieldFormat {  -- modifier characters to find the primary format character.  -- This is the type of its result.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  data FormatParse = FormatParse {    fpModifiers :: String,   -- ^ Any modifiers found.    fpChar :: Char,          -- ^ Primary format character. @@ -486,13 +486,13 @@ parseIntFormat _ s =  -- | This is the type of a field formatter reified over its  -- argument.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  type FieldFormatter = FieldFormat -> ShowS  -- | Type of a function that will parse modifier characters  -- from the format string.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  type ModifierParser = String -> FormatParse  -- | Substitute a \'v\' format character with the given @@ -500,21 +500,21 @@ type ModifierParser = String -> FormatParse  -- convenience for user-implemented types, which should  -- support \"%v\".  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  vFmt :: Char -> FieldFormat -> FieldFormat  vFmt c ufmt@(FieldFormat {fmtChar = 'v'}) = ufmt {fmtChar = c}  vFmt _ ufmt = ufmt  -- | Formatter for 'Char' values.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  formatChar :: Char -> FieldFormatter  formatChar x ufmt =    formatIntegral (Just 0) (toInteger $ ord x) $ vFmt 'c' ufmt  -- | Formatter for 'String' values.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  formatString :: IsChar a => [a] -> FieldFormatter  formatString x ufmt =    case fmtChar $ vFmt 's' ufmt of @@ -539,7 +539,7 @@ fixupMods ufmt m =  -- | Formatter for 'Int' values.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  formatInt :: (Integral a, Bounded a) => a -> FieldFormatter  formatInt x ufmt =    let lb = toInteger $ minBound `asTypeOf` x @@ -552,7 +552,7 @@ formatInt x ufmt =  -- | Formatter for 'Integer' values.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  formatInteger :: Integer -> FieldFormatter  formatInteger x ufmt =    let m = fixupMods ufmt Nothing in @@ -593,7 +593,7 @@ formatIntegral m x ufmt0 =  -- | Formatter for 'RealFloat' values.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  formatRealFloat :: RealFloat a => a -> FieldFormatter  formatRealFloat x ufmt =    let c = fmtChar $ vFmt 'g' ufmt @@ -869,14 +869,14 @@ dfmt c p a d =  -- | Raises an 'error' with a printf-specific prefix on the  -- message string.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  perror :: String -> a  perror s = error $ "printf: " ++ s  -- | Calls 'perror' to indicate an unknown format letter for  -- a given type.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  errorBadFormat :: Char -> a  errorBadFormat c = perror $ "bad formatting char " ++ show c @@ -884,15 +884,15 @@ errorShortFormat, errorMissingArgument, errorBadArgument :: a  -- | Calls 'perror' to indicate that the format string ended  -- early.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  errorShortFormat = perror "formatting string ended prematurely"  -- | Calls 'perror' to indicate that there is a missing  -- argument in the argument list.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  errorMissingArgument = perror "argument list ended prematurely"  -- | Calls 'perror' to indicate that there is a type  -- error or similar in the given argument.  -- --- /Since: 4.7.0.0/ +-- @since 4.7.0.0  errorBadArgument = perror "bad argument" diff --git a/libraries/base/Text/Read.hs b/libraries/base/Text/Read.hs index 1d08343e2c..0e752c2bbb 100644 --- a/libraries/base/Text/Read.hs +++ b/libraries/base/Text/Read.hs @@ -62,7 +62,7 @@ reads = readsPrec minPrec  -- Succeeds if there is exactly one valid result.  -- A 'Left' value indicates a parse error.  -- --- /Since: 4.6.0.0/ +-- @since 4.6.0.0  readEither :: Read a => String -> Either String a  readEither s =    case [ x | (x,"") <- readPrec_to_S read' minPrec s ] of @@ -78,7 +78,7 @@ readEither s =  -- | Parse a string using the 'Read' instance.  -- Succeeds if there is exactly one valid result.  -- --- /Since: 4.6.0.0/ +-- @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 74cf9508e6..2e682ff7e0 100644 --- a/libraries/base/Text/Read/Lex.hs +++ b/libraries/base/Text/Read/Lex.hs @@ -63,11 +63,11 @@ data Lexeme    | Punc   String       -- ^ Punctuation or reserved symbol, e.g. @(@, @::@    | Ident  String       -- ^ Haskell identifier, e.g. @foo@, @Baz@    | Symbol String       -- ^ Haskell symbol, e.g. @>>@, @:%@ -  | Number Number       -- ^ /Since: 4.6.0.0/ +  | Number Number       -- ^ @since 4.6.0.0    | EOF   deriving (Eq, Show) --- | /Since: 4.7.0.0/ +-- | @since 4.7.0.0  data Number = MkNumber Int              -- Base                         Digits           -- Integral part              | MkDecimal Digits          -- Integral part @@ -75,13 +75,13 @@ data Number = MkNumber Int              -- Base                          (Maybe Integer) -- Exponent   deriving (Eq, Show) --- | /Since: 4.5.1.0/ +-- | @since 4.5.1.0  numberToInteger :: Number -> Maybe Integer  numberToInteger (MkNumber base iPart) = Just (val (fromIntegral base) 0 iPart)  numberToInteger (MkDecimal iPart Nothing Nothing) = Just (val 10 0 iPart)  numberToInteger _ = Nothing --- | /Since: 4.7.0.0/ +-- | @since 4.7.0.0  numberToFixed :: Integer -> Number -> Maybe (Integer, Integer)  numberToFixed _ (MkNumber base iPart) = Just (val (fromIntegral base) 0 iPart, 0)  numberToFixed _ (MkDecimal iPart Nothing Nothing) = Just (val 10 0 iPart, 0) @@ -109,7 +109,7 @@ numberToFixed _ _ = Nothing  -- * We only worry about numbers that have an exponent. If they don't  --   have an exponent then the Rational won't be much larger than the  --   Number, so there is no problem --- | /Since: 4.5.1.0/ +-- | @since 4.5.1.0  numberToRangedRational :: (Int, Int) -> Number                         -> Maybe Rational -- Nothing = Inf  numberToRangedRational (neg, pos) n@(MkDecimal iPart mFPart (Just exp)) @@ -139,7 +139,7 @@ numberToRangedRational (neg, pos) n@(MkDecimal iPart mFPart (Just exp))                  else Just (numberToRational n)  numberToRangedRational _ n = Just (numberToRational n) --- | /Since: 4.6.0.0/ +-- | @since 4.6.0.0  numberToRational :: Number -> Rational  numberToRational (MkNumber base iPart) = val (fromIntegral base) 0 iPart % 1  numberToRational (MkDecimal iPart mFPart mExp) @@ -162,7 +162,7 @@ numberToRational (MkDecimal iPart mFPart mExp)  lex :: ReadP Lexeme  lex = skipSpaces >> lexToken --- | /Since: 4.7.0.0/ +-- | @since 4.7.0.0  expect :: Lexeme -> ReadP ()  expect lexeme = do { skipSpaces                     ; thing <- lexToken diff --git a/libraries/ghc-prim/GHC/Types.hs b/libraries/ghc-prim/GHC/Types.hs index 9cc941012b..808e44f137 100644 --- a/libraries/ghc-prim/GHC/Types.hs +++ b/libraries/ghc-prim/GHC/Types.hs @@ -159,7 +159,7 @@ data (~) a b = Eq# ((~#) a b)  --      <http://www.cis.upenn.edu/~eir/papers/2014/coercible/coercible.pdf Safe Coercions>  --      by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich.  -- ---      /Since: 4.7.0.0/ +--      @since 4.7.0.0  data Coercible a b = MkCoercible ((~#) a b)  -- It's really ~R# (representational equality), not ~#,  -- but  * we don't yet have syntax for ~R#, diff --git a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs index 48dd5d22e8..0ad6848974 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/GMP/Internals.hs @@ -190,7 +190,7 @@ default ()  -- * \"@'sizeInBaseInteger' /i/ 2#@\" can be used to determine the most  --   significant bit of @/i/@.  -- --- /Since: 0.5.1.0/ +-- @since 0.5.1.0  sizeInBaseInteger :: Integer -> Int# -> Word#  sizeInBaseInteger (S# i#)  = sizeInBaseWord# (int2Word# (absI# i#))  sizeInBaseInteger (Jp# bn) = sizeInBaseBigNat bn @@ -198,7 +198,7 @@ sizeInBaseInteger (Jn# bn) = sizeInBaseBigNat bn  -- | Version of 'sizeInBaseInteger' operating on 'BigNat'  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  sizeInBaseBigNat :: BigNat -> Int# -> Word#  sizeInBaseBigNat bn@(BN# ba#) = c_mpn_sizeinbase# ba# (sizeofBigNat# bn) @@ -207,7 +207,7 @@ foreign import ccall unsafe "integer_gmp_mpn_sizeinbase"  -- | Version of 'sizeInBaseInteger' operating on 'Word#'  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  foreign import ccall unsafe "integer_gmp_mpn_sizeinbase1"    sizeInBaseWord# :: Word# -> Int# -> Word# @@ -217,7 +217,7 @@ foreign import ccall unsafe "integer_gmp_mpn_sizeinbase1"  --  -- See description of 'exportIntegerToMutableByteArray' for more details.  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  exportIntegerToAddr :: Integer -> Addr# -> Int# -> IO Word  exportIntegerToAddr (S# i#)  = exportWordToAddr (W# (int2Word# (absI# i#)))  exportIntegerToAddr (Jp# bn) = exportBigNatToAddr bn @@ -268,7 +268,7 @@ foreign import ccall unsafe "integer_gmp_mpn_export1"  -- integers as this function would currently convert those to big  -- integers in msbf to call @mpz_export()@.  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  exportIntegerToMutableByteArray :: Integer -> MutableByteArray# RealWorld                                  -> Word# -> Int# -> IO Word  exportIntegerToMutableByteArray (S# i#) @@ -278,7 +278,7 @@ exportIntegerToMutableByteArray (Jn# bn) = exportBigNatToMutableByteArray bn  -- | Version of 'exportIntegerToMutableByteArray' operating on 'BigNat's.  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  exportBigNatToMutableByteArray :: BigNat -> MutableByteArray# RealWorld -> Word#                                 -> Int# -> IO Word  exportBigNatToMutableByteArray bn@(BN# ba#) @@ -291,7 +291,7 @@ foreign import ccall unsafe "integer_gmp_mpn_export"  -- | Version of 'exportIntegerToMutableByteArray' operating on 'Word's.  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  exportWordToMutableByteArray :: Word -> MutableByteArray# RealWorld -> Word#                               -> Int# -> IO Word  exportWordToMutableByteArray (W# w#) = c_mpn_export1ToMutableByteArray# w# @@ -316,7 +316,7 @@ foreign import ccall unsafe "integer_gmp_mpn_export1"  -- determining a /probable prime/. For more details, see  -- <http://gmplib.org/manual/Number-Theoretic-Functions.html#index-mpz_005fprobab_005fprime_005fp-360 GMP documentation for `mpz_probab_prime_p()`>.  -- --- /Since: 0.5.1.0/ +-- @since 0.5.1.0  {-# NOINLINE testPrimeInteger #-}  testPrimeInteger :: Integer -> Int# -> Int#  testPrimeInteger (S# i#) = testPrimeWord# (int2Word# (absI# i#)) @@ -325,7 +325,7 @@ testPrimeInteger (Jn# n) = testPrimeBigNat n  -- | Version of 'testPrimeInteger' operating on 'BigNat's  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  testPrimeBigNat :: BigNat -> Int# -> Int#  testPrimeBigNat bn@(BN# ba#) = c_integer_gmp_test_prime# ba# (sizeofBigNat# bn) @@ -334,7 +334,7 @@ foreign import ccall unsafe "integer_gmp_test_prime"  -- | Version of 'testPrimeInteger' operating on 'Word#'s  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  foreign import ccall unsafe "integer_gmp_test_prime1"    testPrimeWord# :: GmpLimb# -> Int# -> Int# @@ -346,7 +346,7 @@ foreign import ccall unsafe "integer_gmp_test_prime1"  -- primes. For practical purposes it's adequate, the chance of a  -- composite passing will be extremely small.\"  -- --- /Since: 0.5.1.0/ +-- @since 0.5.1.0  {-# NOINLINE nextPrimeInteger #-}  nextPrimeInteger :: Integer -> Integer  nextPrimeInteger (S# i#) @@ -357,6 +357,6 @@ nextPrimeInteger (Jn# _)  = S# 2#  -- | Version of 'nextPrimeInteger' operating on 'Word#'s  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  foreign import ccall unsafe "integer_gmp_next_prime1"    nextPrimeWord# :: GmpLimb# -> GmpLimb# diff --git a/libraries/integer-gmp2/src/GHC/Integer/Type.hs b/libraries/integer-gmp2/src/GHC/Integer/Type.hs index db24560a02..e2028553c4 100644 --- a/libraries/integer-gmp2/src/GHC/Integer/Type.hs +++ b/libraries/integer-gmp2/src/GHC/Integer/Type.hs @@ -785,7 +785,7 @@ gcdInt x# y#  -- | Compute greatest common divisor.  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  gcdWord :: Word# -> Word# -> Word#  gcdWord = gcdWord# @@ -1261,7 +1261,7 @@ gcdBigNat x@(BN# x#) y@(BN# y#)  -- For @/a/@ and @/b/@, compute their greatest common divisor @/g/@  -- and the coefficient @/s/@ satisfying @/a//s/ + /b//t/ = /g/@.  -- --- /Since: 0.5.1.0/ +-- @since 0.5.1.0  {-# NOINLINE gcdExtInteger #-}  gcdExtInteger :: Integer -> Integer -> (# Integer, Integer #)  gcdExtInteger a b = case gcdExtSBigNat a' b' of @@ -1312,7 +1312,7 @@ gcdExtSBigNat x y = case runS go of (g,s) -> (# g, s #)  -- Future versions of @integer_gmp@ may not support negative @/e/@  -- values anymore.  -- --- /Since: 0.5.1.0/ +-- @since 0.5.1.0  {-# NOINLINE powModInteger #-}  powModInteger :: Integer -> Integer -> Integer -> Integer  powModInteger (S# b#) (S# e#) (S# m#) @@ -1329,19 +1329,19 @@ powModInteger b e m = case m of  -- | Version of 'powModInteger' operating on 'BigNat's  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  powModBigNat :: BigNat -> BigNat -> BigNat -> BigNat  powModBigNat b e m = inline powModSBigNat (PosBN b) (PosBN e) m  -- | Version of 'powModInteger' for 'Word#'-sized moduli  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  powModBigNatWord :: BigNat -> BigNat -> GmpLimb# -> GmpLimb#  powModBigNatWord b e m# = inline powModSBigNatWord (PosBN b) (PosBN e) m#  -- | Version of 'powModInteger' operating on 'Word#'s  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  foreign import ccall unsafe "integer_gmp_powm_word"    powModWord :: GmpLimb# -> GmpLimb# -> GmpLimb# -> GmpLimb# @@ -1384,7 +1384,7 @@ foreign import ccall unsafe "integer_gmp_powm1"  -- the inverse exists, the return value @/y/@ will satisfy @0 < /y/ <  -- abs(/m/)@, otherwise the result is @0@.  -- --- /Since: 0.5.1.0/ +-- @since 0.5.1.0  {-# NOINLINE recipModInteger #-}  recipModInteger :: Integer -> Integer -> Integer  recipModInteger (S# x#) (S# m#) @@ -1397,13 +1397,13 @@ recipModInteger x m = bigNatToInteger (recipModSBigNat x' m')  -- | Version of 'recipModInteger' operating on 'BigNat's  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  recipModBigNat :: BigNat -> BigNat -> BigNat  recipModBigNat x m = inline recipModSBigNat (PosBN x) m  -- | Version of 'recipModInteger' operating on 'Word#'s  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  foreign import ccall unsafe "integer_gmp_invert_word"    recipModWord :: GmpLimb# -> GmpLimb# -> GmpLimb# @@ -1748,7 +1748,7 @@ byteArrayToBigNat# ba# n0#  --  -- See description of 'importIntegerFromByteArray' for more details.  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  importIntegerFromAddr :: Addr# -> Word# -> Int# -> IO Integer  importIntegerFromAddr addr len msbf = IO $ do      bn <- liftIO (importBigNatFromAddr addr len msbf) @@ -1802,7 +1802,7 @@ foreign import ccall unsafe "integer_gmp_mpn_import"  --  -- * returns a new 'Integer'  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  importIntegerFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> Integer  importIntegerFromByteArray ba ofs len msbf      = bigNatToInteger (importBigNatFromByteArray ba ofs len msbf) @@ -1860,7 +1860,7 @@ isValidBigNat# (BN# ba#)  -- | Version of 'nextPrimeInteger' operating on 'BigNat's  -- --- /Since: 1.0.0.0/ +-- @since 1.0.0.0  nextPrimeBigNat :: BigNat -> BigNat  nextPrimeBigNat bn@(BN# ba#) = runS $ do      mbn@(MBN# mba#) <- newBigNat# n# | 
