diff options
| -rw-r--r-- | libraries/base/Control/Concurrent/Chan.hs | 4 | ||||
| -rw-r--r-- | libraries/base/Control/Concurrent/MVar.hs | 2 | ||||
| -rw-r--r-- | libraries/base/Control/Monad/Instances.hs | 2 | ||||
| -rw-r--r-- | libraries/base/Control/Monad/ST.hs | 4 | ||||
| -rw-r--r-- | libraries/base/Control/Monad/ST/Lazy.hs | 4 | ||||
| -rw-r--r-- | libraries/base/Data/Bits.hs | 2 | ||||
| -rw-r--r-- | libraries/base/Data/OldTypeable.hs | 6 | ||||
| -rw-r--r-- | libraries/base/Data/OldTypeable/Internal.hs | 4 | ||||
| -rw-r--r-- | libraries/base/Data/Typeable/Internal.hs | 2 | ||||
| -rw-r--r-- | libraries/base/Debug/Trace.hs | 2 | ||||
| -rw-r--r-- | libraries/base/Foreign.hs | 2 | ||||
| -rw-r--r-- | libraries/base/Foreign/ForeignPtr.hs | 2 | ||||
| -rw-r--r-- | libraries/base/Foreign/Marshal.hs | 4 | ||||
| -rw-r--r-- | libraries/base/Foreign/Marshal/Error.hs | 2 | ||||
| -rw-r--r-- | libraries/base/GHC/Conc/Sync.lhs | 8 | ||||
| -rwxr-xr-x | libraries/base/GHC/Exts.hs | 2 | ||||
| -rw-r--r-- | libraries/base/GHC/Generics.hs | 4 | ||||
| -rw-r--r-- | libraries/base/GHC/IO.hs | 6 | 
18 files changed, 28 insertions, 34 deletions
| diff --git a/libraries/base/Control/Concurrent/Chan.hs b/libraries/base/Control/Concurrent/Chan.hs index 5781b9f476..ca4c17cffb 100644 --- a/libraries/base/Control/Concurrent/Chan.hs +++ b/libraries/base/Control/Concurrent/Chan.hs @@ -142,7 +142,7 @@ unGetChan (Chan readVar _) val = do     modifyMVar_ readVar $ \read_end -> do       putMVar new_read_end (ChItem val read_end)       return new_read_end -{-# DEPRECATED unGetChan "if you need this operation, use Control.Concurrent.STM.TChan instead.  See http://hackage.haskell.org/trac/ghc/ticket/4154 for details" #-} +{-# DEPRECATED unGetChan "if you need this operation, use Control.Concurrent.STM.TChan instead.  See http://hackage.haskell.org/trac/ghc/ticket/4154 for details" #-} -- deprecated in 7.0  -- |Returns 'True' if the supplied 'Chan' is empty.  isEmptyChan :: Chan a -> IO Bool @@ -151,7 +151,7 @@ isEmptyChan (Chan readVar writeVar) = do       w <- readMVar writeVar       let eq = r == w       eq `seq` return eq -{-# DEPRECATED isEmptyChan "if you need this operation, use Control.Concurrent.STM.TChan instead.  See http://hackage.haskell.org/trac/ghc/ticket/4154 for details" #-} +{-# DEPRECATED isEmptyChan "if you need this operation, use Control.Concurrent.STM.TChan instead.  See http://hackage.haskell.org/trac/ghc/ticket/4154 for details" #-} -- deprecated in 7.0  -- Operators for interfacing with functional streams. diff --git a/libraries/base/Control/Concurrent/MVar.hs b/libraries/base/Control/Concurrent/MVar.hs index 5f1b4fce6e..f941be9089 100644 --- a/libraries/base/Control/Concurrent/MVar.hs +++ b/libraries/base/Control/Concurrent/MVar.hs @@ -263,7 +263,7 @@ modifyMVarMasked m io =      putMVar m a'      return b -{-# DEPRECATED addMVarFinalizer "use mkWeakMVar instead" #-} +{-# DEPRECATED addMVarFinalizer "use mkWeakMVar instead" #-} -- deprecated in 7.6  addMVarFinalizer :: MVar a -> IO () -> IO ()  addMVarFinalizer = GHC.MVar.addMVarFinalizer diff --git a/libraries/base/Control/Monad/Instances.hs b/libraries/base/Control/Monad/Instances.hs index 7c31b3457c..353f1c4a10 100644 --- a/libraries/base/Control/Monad/Instances.hs +++ b/libraries/base/Control/Monad/Instances.hs @@ -16,5 +16,5 @@  -- 'Functor' instances for @(,) a@ and @'Either' a@.  module Control.Monad.Instances (Functor(..),Monad(..)) where - +-- module DEPRECATED -- deprecated in 7.6  import Prelude diff --git a/libraries/base/Control/Monad/ST.hs b/libraries/base/Control/Monad/ST.hs index fe8a837cda..6113055864 100644 --- a/libraries/base/Control/Monad/ST.hs +++ b/libraries/base/Control/Monad/ST.hs @@ -39,9 +39,7 @@ module Control.Monad.ST (  import Control.Monad.ST.Safe  import qualified Control.Monad.ST.Unsafe as U -{-# DEPRECATED unsafeInterleaveST, unsafeIOToST, unsafeSTToIO -              "Please import from Control.Monad.ST.Unsafe instead; This will be removed in the next release" - #-} +{-# DEPRECATED unsafeInterleaveST, unsafeIOToST, unsafeSTToIO "Please import from Control.Monad.ST.Unsafe instead; This will be removed in the next release" #-} -- deprecated in 7.2  {-# INLINE unsafeInterleaveST #-}  unsafeInterleaveST :: ST s a -> ST s a diff --git a/libraries/base/Control/Monad/ST/Lazy.hs b/libraries/base/Control/Monad/ST/Lazy.hs index 400addd696..26effa4630 100644 --- a/libraries/base/Control/Monad/ST/Lazy.hs +++ b/libraries/base/Control/Monad/ST/Lazy.hs @@ -37,9 +37,7 @@ module Control.Monad.ST.Lazy (  import Control.Monad.ST.Lazy.Safe  import qualified Control.Monad.ST.Lazy.Unsafe as U -{-# DEPRECATED unsafeInterleaveST, unsafeIOToST -              "Please import from Control.Monad.ST.Lazy.Unsafe instead; This will be removed in the next release" - #-} +{-# DEPRECATED unsafeInterleaveST, unsafeIOToST "Please import from Control.Monad.ST.Lazy.Unsafe instead; This will be removed in the next release" #-} -- deprecated in 7.2  {-# INLINE unsafeInterleaveST #-}  unsafeInterleaveST :: ST s a -> ST s a diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index 63e6b811c4..2385ab9ae5 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -69,7 +69,7 @@ infixl 7 .&.  infixl 6 `xor`  infixl 5 .|. -{-# DEPRECATED bitSize "Use bitSizeMaybe or finiteBitSize instead" #-} +{-# DEPRECATED bitSize "Use bitSizeMaybe or finiteBitSize instead" #-} -- deprecated in 7.8  {-|   The 'Bits' class defines bitwise operations over integral types. diff --git a/libraries/base/Data/OldTypeable.hs b/libraries/base/Data/OldTypeable.hs index 2d5f0d464d..bed7ad15ab 100644 --- a/libraries/base/Data/OldTypeable.hs +++ b/libraries/base/Data/OldTypeable.hs @@ -30,7 +30,7 @@  --  ----------------------------------------------------------------------------- -module Data.OldTypeable {-# DEPRECATED "Use Data.Typeable instead" #-} +module Data.OldTypeable {-# DEPRECATED "Use Data.Typeable instead" #-} -- deprecated in 7.8    (          -- * The Typeable class @@ -121,7 +121,7 @@ import Hugs.ConcBase    ( MVar )  #include "OldTypeable.h" -{-# DEPRECATED typeRepKey "TypeRep itself is now an instance of Ord" #-} +{-# DEPRECATED typeRepKey "TypeRep itself is now an instance of Ord" #-} -- deprecated in 7.2  -- | (DEPRECATED) Returns a unique key associated with a 'TypeRep'.  -- This function is deprecated because 'TypeRep' itself is now an  -- instance of 'Ord', so mappings can be made directly with 'TypeRep' @@ -146,7 +146,7 @@ newtype TypeRepKey = TypeRepKey Fingerprint  ----------------- Construction --------------------- -{-# DEPRECATED mkTyCon "either derive Typeable, or use mkTyCon3 instead" #-} +{-# DEPRECATED mkTyCon "either derive Typeable, or use mkTyCon3 instead" #-} -- deprecated in 7.2  -- | Backwards-compatible API  mkTyCon :: String       -- ^ unique string          -> TyCon        -- ^ A unique 'TyCon' object diff --git a/libraries/base/Data/OldTypeable/Internal.hs b/libraries/base/Data/OldTypeable/Internal.hs index 96bbf0ba62..5c261307f1 100644 --- a/libraries/base/Data/OldTypeable/Internal.hs +++ b/libraries/base/Data/OldTypeable/Internal.hs @@ -22,7 +22,7 @@  {-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}  #endif -module Data.OldTypeable.Internal {-# DEPRECATED "Use Data.Typeable.Internal instead" #-} ( +module Data.OldTypeable.Internal {-# DEPRECATED "Use Data.Typeable.Internal instead" #-} ( -- deprecated in 7.8      TypeRep(..),      TyCon(..),      mkTyCon, @@ -189,7 +189,7 @@ typeRepArgs :: TypeRep -> [TypeRep]  typeRepArgs (TypeRep _ _ args) = args  -- | Observe string encoding of a type representation -{-# DEPRECATED tyConString "renamed to tyConName; tyConModule and tyConPackage are also available." #-} +{-# DEPRECATED tyConString "renamed to tyConName; tyConModule and tyConPackage are also available." #-} -- deprecated in 7.4  tyConString :: TyCon   -> String  tyConString = tyConName diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 8749275554..440c4e869b 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -178,7 +178,7 @@ typeRepArgs :: TypeRep -> [TypeRep]  typeRepArgs (TypeRep _ _ args) = args  -- | Observe string encoding of a type representation -{-# DEPRECATED tyConString "renamed to tyConName; tyConModule and tyConPackage are also available." #-} +{-# DEPRECATED tyConString "renamed to tyConName; tyConModule and tyConPackage are also available." #-} -- deprecated in 7.4  tyConString :: TyCon   -> String  tyConString = tyConName diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs index f5839eead2..94568d217b 100644 --- a/libraries/base/Debug/Trace.hs +++ b/libraries/base/Debug/Trace.hs @@ -86,7 +86,7 @@ foreign import ccall unsafe "HsBase.h debugBelch2"  -- | Deprecated. Use 'traceIO'.  putTraceMsg :: String -> IO ()  putTraceMsg = traceIO -{-# DEPRECATED putTraceMsg "Use Debug.Trace.traceIO" #-} +{-# DEPRECATED putTraceMsg "Use Debug.Trace.traceIO" #-} -- deprecated in 7.4  {-# NOINLINE trace #-} diff --git a/libraries/base/Foreign.hs b/libraries/base/Foreign.hs index caad10442e..dbdc90588b 100644 --- a/libraries/base/Foreign.hs +++ b/libraries/base/Foreign.hs @@ -47,7 +47,7 @@ import Foreign.Marshal  import GHC.IO (IO)  import qualified GHC.IO (unsafePerformIO) -{-# DEPRECATED unsafePerformIO "Use System.IO.Unsafe.unsafePerformIO instead; This function will be removed in the next release" #-} +{-# DEPRECATED unsafePerformIO "Use System.IO.Unsafe.unsafePerformIO instead; This function will be removed in the next release" #-} -- deprecated in 7.2  {-# INLINE unsafePerformIO #-}  unsafePerformIO :: IO a -> a diff --git a/libraries/base/Foreign/ForeignPtr.hs b/libraries/base/Foreign/ForeignPtr.hs index 5288ce7718..be6dec0459 100644 --- a/libraries/base/Foreign/ForeignPtr.hs +++ b/libraries/base/Foreign/ForeignPtr.hs @@ -57,7 +57,7 @@ import Foreign.ForeignPtr.Safe  import Foreign.Ptr ( Ptr )  import qualified Foreign.ForeignPtr.Unsafe as U -{-# DEPRECATED unsafeForeignPtrToPtr "Use Foreign.ForeignPtr.Unsafe.unsafeForeignPtrToPtr instead; This function will be removed in the next release" #-} +{-# DEPRECATED unsafeForeignPtrToPtr "Use Foreign.ForeignPtr.Unsafe.unsafeForeignPtrToPtr instead; This function will be removed in the next release" #-} -- deprecated in 7.2  {-# INLINE unsafeForeignPtrToPtr #-}  unsafeForeignPtrToPtr :: ForeignPtr a -> Ptr a  unsafeForeignPtrToPtr = U.unsafeForeignPtrToPtr diff --git a/libraries/base/Foreign/Marshal.hs b/libraries/base/Foreign/Marshal.hs index cb0ef415fe..ef81cec75e 100644 --- a/libraries/base/Foreign/Marshal.hs +++ b/libraries/base/Foreign/Marshal.hs @@ -50,9 +50,7 @@ results in undefined behaviour.  It is expected that this operation will be  replaced in a future revision of Haskell.  -} -{-# DEPRECATED unsafeLocalState -               "Please import from Foreign.Marshall.Unsafe instead; This will be removed in the next release" - #-} +{-# DEPRECATED unsafeLocalState "Please import from Foreign.Marshall.Unsafe instead; This will be removed in the next release" #-} -- deprecated in 7.2  unsafeLocalState :: IO a -> a  unsafeLocalState = unsafePerformIO diff --git a/libraries/base/Foreign/Marshal/Error.hs b/libraries/base/Foreign/Marshal/Error.hs index 3048ffe063..e26716cfdf 100644 --- a/libraries/base/Foreign/Marshal/Error.hs +++ b/libraries/base/Foreign/Marshal/Error.hs @@ -81,4 +81,4 @@ throwIfNull  = throwIf (== nullPtr) . const  --  void     :: IO a -> IO ()  void act  = act >> return () -{-# DEPRECATED void "use Control.Monad.void instead" #-} +{-# DEPRECATED void "use Control.Monad.void instead" #-} -- deprecated in 7.6 diff --git a/libraries/base/GHC/Conc/Sync.lhs b/libraries/base/GHC/Conc/Sync.lhs index 6646e7c9eb..7c6c1b6d46 100644 --- a/libraries/base/GHC/Conc/Sync.lhs +++ b/libraries/base/GHC/Conc/Sync.lhs @@ -45,7 +45,7 @@ module GHC.Conc.Sync          , forkIOUnmasked          , forkIOWithUnmask          , forkOn -        , forkOnIO    -- DEPRECATED +        , forkOnIO    -- DEPRECATED -- deprecated in 7.2          , forkOnIOUnmasked          , forkOnWithUnmask          , numCapabilities @@ -208,7 +208,7 @@ forkIO action = IO $ \ s ->   where    action_plus = catchException action childHandler -{-# DEPRECATED forkIOUnmasked "use forkIOWithUnmask instead" #-} +{-# DEPRECATED forkIOUnmasked "use forkIOWithUnmask instead" #-} -- deprecated in 7.2  -- | This function is deprecated; use 'forkIOWithUnmask' instead  forkIOUnmasked :: IO () -> IO ThreadId  forkIOUnmasked io = forkIO (unsafeUnmask io) @@ -258,12 +258,12 @@ forkOn (I# cpu) action = IO $ \ s ->   where    action_plus = catchException action childHandler -{-# DEPRECATED forkOnIO "renamed to forkOn" #-} +{-# DEPRECATED forkOnIO "renamed to forkOn" #-} -- deprecated in 7.2  -- | This function is deprecated; use 'forkOn' instead  forkOnIO :: Int -> IO () -> IO ThreadId  forkOnIO = forkOn -{-# DEPRECATED forkOnIOUnmasked "use forkOnWithUnmask instead" #-} +{-# DEPRECATED forkOnIOUnmasked "use forkOnWithUnmask instead" #-} -- deprecated in 7.2  -- | This function is deprecated; use 'forkOnWIthUnmask' instead  forkOnIOUnmasked :: Int -> IO () -> IO ThreadId  forkOnIOUnmasked cpu io = forkOn cpu (unsafeUnmask io) diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs index 819172050b..5639e13e69 100755 --- a/libraries/base/GHC/Exts.hs +++ b/libraries/base/GHC/Exts.hs @@ -113,7 +113,7 @@ groupByFB c n eq xs0 = groupByFBCore xs0  traceEvent :: String -> IO ()  traceEvent = Debug.Trace.traceEventIO -{-# DEPRECATED traceEvent "Use Debug.Trace.traceEvent or Debug.Trace.traceEventIO" #-} +{-# DEPRECATED traceEvent "Use Debug.Trace.traceEvent or Debug.Trace.traceEventIO" #-} -- deprecated in 7.4  {- ********************************************************************** diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs index 672e72553c..e669af3625 100644 --- a/libraries/base/GHC/Generics.hs +++ b/libraries/base/GHC/Generics.hs @@ -105,8 +105,8 @@ data P  type Rec0  = K1 R  -- | Type synonym for encoding parameters (other than the last)  type Par0  = K1 P -{-# DEPRECATED Par0 "Par0 is no longer used; use Rec0 instead" #-} -{-# DEPRECATED P "P is no longer used; use R instead" #-} +{-# DEPRECATED Par0 "Par0 is no longer used; use Rec0 instead" #-} -- deprecated in 7.6 +{-# DEPRECATED P "P is no longer used; use R instead" #-} -- deprecated in 7.6  -- | Tag for M1: datatype  data D diff --git a/libraries/base/GHC/IO.hs b/libraries/base/GHC/IO.hs index 0a39e40dd3..c5239a4f9e 100644 --- a/libraries/base/GHC/IO.hs +++ b/libraries/base/GHC/IO.hs @@ -302,7 +302,7 @@ throwIO e = IO (raiseIO# (toException e))  -- -----------------------------------------------------------------------------  -- Controlling asynchronous exception delivery -{-# DEPRECATED block "use Control.Exception.mask instead" #-} +{-# DEPRECATED block "use Control.Exception.mask instead" #-} -- deprecated in 7.0  -- | Note: this function is deprecated, please use 'mask' instead.  --  -- Applying 'block' to a computation will @@ -322,7 +322,7 @@ throwIO e = IO (raiseIO# (toException e))  block :: IO a -> IO a  block (IO io) = IO $ maskAsyncExceptions# io -{-# DEPRECATED unblock "use Control.Exception.mask instead" #-} +{-# DEPRECATED unblock "use Control.Exception.mask instead" #-} -- deprecated in 7.0  -- | Note: this function is deprecated, please use 'mask' instead.  --  -- To re-enable asynchronous exceptions inside the scope of @@ -358,7 +358,7 @@ getMaskingState  = IO $ \s ->                               1# -> MaskedUninterruptible                               _  -> MaskedInterruptible #) -{-# DEPRECATED blocked "use Control.Exception.getMaskingState instead" #-} +{-# DEPRECATED blocked "use Control.Exception.getMaskingState instead" #-} -- deprecated in 7.2  -- | returns True if asynchronous exceptions are blocked in the  -- current thread.  blocked :: IO Bool | 
