[commit: ghc] master: base: replace ver 4.7.1.0 references by 4.8.0.0 (68ecc57)

git at git.haskell.org git at git.haskell.org
Tue Sep 9 16:50:50 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/68ecc578c800aa2767dbf48863f4742859b1a8ec/ghc

>---------------------------------------------------------------

commit 68ecc578c800aa2767dbf48863f4742859b1a8ec
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Tue Sep 9 18:46:10 2014 +0200

    base: replace ver 4.7.1.0 references by 4.8.0.0
    
    Since we now had to major bump due to AMP being landed, `base-4.7.1.0` is not
    gonna happen, as we're going straight for a `base-4.8.0.0` release.
    
    [skip ci] since this is a doc-only change


>---------------------------------------------------------------

68ecc578c800aa2767dbf48863f4742859b1a8ec
 libraries/base/Control/Monad.hs | 2 +-
 libraries/base/Data/Function.hs | 2 +-
 libraries/base/Data/List.hs     | 2 +-
 libraries/base/GHC/TypeLits.hs  | 4 ++--
 libraries/base/System/Exit.hs   | 2 +-
 libraries/base/changelog.md     | 4 +++-
 6 files changed, 9 insertions(+), 7 deletions(-)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index bfadd7c..532c42c 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -335,7 +335,7 @@ infixl 4 <$!>
 
 -- | Strict version of 'Data.Functor.<$>'.
 --
--- /Since: 4.7.1.0/
+-- /Since: 4.8.0.0/
 (<$!>) :: Monad m => (a -> b) -> m a -> m b
 {-# INLINE (<$!>) #-}
 f <$!> m = do
diff --git a/libraries/base/Data/Function.hs b/libraries/base/Data/Function.hs
index afb6e56..a3fac7c 100644
--- a/libraries/base/Data/Function.hs
+++ b/libraries/base/Data/Function.hs
@@ -94,6 +94,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.7.1.0/
+-- /Since: 4.8.0.0/
 (&) :: a -> (a -> b) -> b
 x & f = f x
diff --git a/libraries/base/Data/List.hs b/libraries/base/Data/List.hs
index f7b58c1..5e5acc1 100644
--- a/libraries/base/Data/List.hs
+++ b/libraries/base/Data/List.hs
@@ -967,7 +967,7 @@ rqpart cmp x (y:ys) rle rgt r =
 -- input list.  This is called the decorate-sort-undecorate paradigm, or
 -- Schwartzian transform.
 --
--- /Since: 4.7.1.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/GHC/TypeLits.hs b/libraries/base/GHC/TypeLits.hs
index 7ae6fb0..cd404f1 100644
--- a/libraries/base/GHC/TypeLits.hs
+++ b/libraries/base/GHC/TypeLits.hs
@@ -81,12 +81,12 @@ symbolVal :: forall n proxy. KnownSymbol n => proxy n -> String
 symbolVal _ = case symbolSing :: SSymbol n of
                 SSymbol x -> x
 
--- | /Since: 4.7.1.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.7.1.0/
+-- | /Since: 4.8.0.0/
 symbolVal' :: forall n. KnownSymbol n => Proxy# n -> String
 symbolVal' _ = case symbolSing :: SSymbol n of
                 SSymbol x -> x
diff --git a/libraries/base/System/Exit.hs b/libraries/base/System/Exit.hs
index 932cbfb..33cc4e8 100644
--- a/libraries/base/System/Exit.hs
+++ b/libraries/base/System/Exit.hs
@@ -78,6 +78,6 @@ exitSuccess = exitWith ExitSuccess
 
 -- | Write given error message to `stderr` and terminate with `exitFailure`.
 --
--- /Since: 4.7.1.0/
+-- /Since: 4.8.0.0/
 die :: String -> IO a
 die err = hPutStrLn stderr err >> exitFailure
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index 4b97c58..6f3c8cc 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -1,9 +1,11 @@
 # Changelog for [`base` package](http://hackage.haskell.org/package/base)
 
-## 4.7.1.0 *TBA*
+## 4.8.0.0  *TBA*
 
   * Bundled with GHC 7.10.1
 
+  * Make `Applicative` a superclass of `Monad`
+
   * Add reverse application operator `Data.Function.(&)`
 
   * Add `Data.List.sortOn` sorting function



More information about the ghc-commits mailing list