summaryrefslogtreecommitdiff
path: root/libraries/base/Data
diff options
context:
space:
mode:
authorHerbert Valerio Riedel <hvr@gnu.org>2014-12-16 12:07:10 +0100
committerHerbert Valerio Riedel <hvr@gnu.org>2014-12-16 13:30:08 +0100
commit554aedab646075e12e53b44df04bcfbccbe03a73 (patch)
tree0832201a44fd74632bbbd88fb77cb6c11eb34cf7 /libraries/base/Data
parent45a9696c550c5fe5e891b6d4710179272dc9f6db (diff)
downloadhaskell-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`)
Diffstat (limited to 'libraries/base/Data')
-rw-r--r--libraries/base/Data/Bifunctor.hs4
-rw-r--r--libraries/base/Data/Bits.hs28
-rw-r--r--libraries/base/Data/Bool.hs2
-rw-r--r--libraries/base/Data/Coerce.hs2
-rw-r--r--libraries/base/Data/Either.hs4
-rw-r--r--libraries/base/Data/Fixed.hs2
-rw-r--r--libraries/base/Data/Function.hs2
-rw-r--r--libraries/base/Data/Functor.hs2
-rw-r--r--libraries/base/Data/Functor/Identity.hs4
-rw-r--r--libraries/base/Data/IORef.hs6
-rw-r--r--libraries/base/Data/List.hs2
-rw-r--r--libraries/base/Data/Monoid.hs4
-rw-r--r--libraries/base/Data/OldList.hs4
-rw-r--r--libraries/base/Data/Ord.hs2
-rw-r--r--libraries/base/Data/Proxy.hs2
-rw-r--r--libraries/base/Data/STRef.hs2
-rw-r--r--libraries/base/Data/Type/Bool.hs2
-rw-r--r--libraries/base/Data/Type/Coercion.hs4
-rw-r--r--libraries/base/Data/Type/Equality.hs4
-rw-r--r--libraries/base/Data/Typeable.hs2
-rw-r--r--libraries/base/Data/Typeable/Internal.hs8
-rw-r--r--libraries/base/Data/Void.hs8
22 files changed, 50 insertions, 50 deletions
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