[commit: ghc] master: base: Update `@since 4.8.2` annotations (re #11026) (5065cf4)
git at git.haskell.org
git at git.haskell.org
Mon Nov 2 14:42:07 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/5065cf490ccdf03dda1e148afb979b8838e6c32e/ghc
>---------------------------------------------------------------
commit 5065cf490ccdf03dda1e148afb979b8838e6c32e
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Mon Nov 2 15:39:28 2015 +0100
base: Update `@since 4.8.2` annotations (re #11026)
This missed to perform in f8ba4b55cc3a061458f5cfabf17de96128defbbb
>---------------------------------------------------------------
5065cf490ccdf03dda1e148afb979b8838e6c32e
libraries/base/Data/List/NonEmpty.hs | 4 ++--
libraries/base/Data/Semigroup.hs | 4 ++--
libraries/base/GHC/Exception.hs | 6 +++---
libraries/base/GHC/IO.hs | 2 +-
libraries/base/GHC/IO/Encoding/Latin1.hs | 4 ++--
libraries/base/GHC/RTS/Flags.hsc | 12 ++++++------
libraries/base/GHC/Stack/Types.hs | 4 ++--
7 files changed, 18 insertions(+), 18 deletions(-)
diff --git a/libraries/base/Data/List/NonEmpty.hs b/libraries/base/Data/List/NonEmpty.hs
index 9bcdcbf..a66ea8f 100644
--- a/libraries/base/Data/List/NonEmpty.hs
+++ b/libraries/base/Data/List/NonEmpty.hs
@@ -19,7 +19,7 @@
-- and in terms of API. You will almost certainly want to import this
-- module @qualified at .
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
----------------------------------------------------------------------------
module Data.List.NonEmpty (
@@ -118,7 +118,7 @@ infixr 5 :|, <|
-- | Non-empty (and non-strict) list type.
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
data NonEmpty a = a :| [a]
deriving ( Eq, Ord, Show, Read, Data, Generic, Generic1 )
diff --git a/libraries/base/Data/Semigroup.hs b/libraries/base/Data/Semigroup.hs
index f3f9f0b..6c92df9 100644
--- a/libraries/base/Data/Semigroup.hs
+++ b/libraries/base/Data/Semigroup.hs
@@ -31,7 +31,7 @@
--
-- > import Data.Semigroup
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
----------------------------------------------------------------------------
module Data.Semigroup (
Semigroup(..)
@@ -86,7 +86,7 @@ infixr 6 <>
-- | The class of semigroups (types with an associative binary operation).
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
class Semigroup a where
-- | An associative operation.
--
diff --git a/libraries/base/GHC/Exception.hs b/libraries/base/GHC/Exception.hs
index 02c6cfa..20b487c 100644
--- a/libraries/base/GHC/Exception.hs
+++ b/libraries/base/GHC/Exception.hs
@@ -186,7 +186,7 @@ errorCallWithCallStackException s stk
-- | Pretty print 'SrcLoc'
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
showSrcLoc :: SrcLoc -> String
showSrcLoc SrcLoc {..}
= foldr (++) ""
@@ -198,7 +198,7 @@ showSrcLoc SrcLoc {..}
-- | Pretty print 'CallStack'
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
showCallStack :: CallStack -> String
showCallStack (CallStack stk@(_:_))
= unlines ("CallStack:" : map (indent . showCallSite) stk)
@@ -214,7 +214,7 @@ showCallStack _ = error "CallStack cannot be empty!"
-- | Remove the most recent callsite from the 'CallStack'
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
popCallStack :: CallStack -> CallStack
popCallStack (CallStack (_:rest)) = CallStack rest
popCallStack _ = error "CallStack cannot be empty!"
diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs
index e41a35d..9fa0aff 100644
--- a/libraries/base/GHC/IO.hs
+++ b/libraries/base/GHC/IO.hs
@@ -348,7 +348,7 @@ unsafeUnmask (IO io) = IO $ unmaskAsyncExceptions# io
-- When called outside 'mask', or inside 'uninterruptibleMask', this
-- function has no effect.
--
--- /Since: 4.8.2.0/
+-- @since 4.9.0.0
interruptible :: IO a -> IO a
interruptible act = do
st <- getMaskingState
diff --git a/libraries/base/GHC/IO/Encoding/Latin1.hs b/libraries/base/GHC/IO/Encoding/Latin1.hs
index d24fcdf..efef240 100644
--- a/libraries/base/GHC/IO/Encoding/Latin1.hs
+++ b/libraries/base/GHC/IO/Encoding/Latin1.hs
@@ -96,11 +96,11 @@ latin1_checked_EF cfm =
-- -----------------------------------------------------------------------------
-- ASCII
--- | @since 4.8.2.0
+-- | @since 4.9.0.0
ascii :: TextEncoding
ascii = mkAscii ErrorOnCodingFailure
--- | @since 4.8.2.0
+-- | @since 4.9.0.0
mkAscii :: CodingFailureMode -> TextEncoding
mkAscii cfm = TextEncoding { textEncodingName = "ASCII",
mkTextDecoder = ascii_DF cfm,
diff --git a/libraries/base/GHC/RTS/Flags.hsc b/libraries/base/GHC/RTS/Flags.hsc
index 62e720f..3708331 100644
--- a/libraries/base/GHC/RTS/Flags.hsc
+++ b/libraries/base/GHC/RTS/Flags.hsc
@@ -55,18 +55,18 @@ import GHC.Word
-- | @'Time'@ is defined as a @'StgWord64'@ in @stg/Types.h@
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
type RtsTime = Word64
-- | @'nat'@ defined in @rts/Types.h@
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
type RtsNat = #{type unsigned int}
-- | Should we produce a summary of the garbage collector statistics after the
-- program has exited?
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
data GiveGCStats
= NoGCStats
| CollectGCStats
@@ -164,7 +164,7 @@ data DebugFlags = DebugFlags
-- | Should the RTS produce a cost-center summary?
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
data DoCostCentres
= CostCentresNone
| CostCentresSummary
@@ -198,7 +198,7 @@ data CCFlags = CCFlags
-- | What sort of heap profile are we collecting?
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
data DoHeapProfile
= NoHeapProfiling
| HeapByCCS
@@ -252,7 +252,7 @@ data ProfFlags = ProfFlags
-- | Is event tracing enabled?
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
data DoTrace
= TraceNone -- ^ no tracing
| TraceEventLog -- ^ send tracing events to the event log
diff --git a/libraries/base/GHC/Stack/Types.hs b/libraries/base/GHC/Stack/Types.hs
index d3ea1d2..a43fe9a 100644
--- a/libraries/base/GHC/Stack/Types.hs
+++ b/libraries/base/GHC/Stack/Types.hs
@@ -71,13 +71,13 @@ import GHC.Integer ()
-- function that was called, the 'SrcLoc' is the call-site. The list is
-- ordered with the most recently called function at the head.
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
data CallStack = CallStack { getCallStack :: [([Char], SrcLoc)] }
-- See Note [Overview of implicit CallStacks]
-- | A single location in the source code.
--
--- @since 4.8.2.0
+-- @since 4.9.0.0
data SrcLoc = SrcLoc
{ srcLocPackage :: [Char]
, srcLocModule :: [Char]
More information about the ghc-commits
mailing list