Repository : ssh://darcs.haskell.org//srv/darcs/packages/base On branch : master
http://hackage.haskell.org/trac/ghc/changeset/00c0ee70fa4a8d14e583554584dc93704a69ba13 >--------------------------------------------------------------- commit 00c0ee70fa4a8d14e583554584dc93704a69ba13 Author: Ian Lynagh <[email protected]> Date: Thu Sep 20 18:53:52 2012 +0100 Remove GHC.IOBase It's been deprecated since at least GHC 6.12 >--------------------------------------------------------------- GHC/IOBase.hs | 93 --------------------------------------------------------- base.cabal | 1 - 2 files changed, 0 insertions(+), 94 deletions(-) diff --git a/GHC/IOBase.hs b/GHC/IOBase.hs deleted file mode 100644 index 60fb943..0000000 --- a/GHC/IOBase.hs +++ /dev/null @@ -1,93 +0,0 @@ -{-# LANGUAGE Unsafe #-} -{-# LANGUAGE DeriveDataTypeable #-} -{-# OPTIONS_HADDOCK hide #-} - ------------------------------------------------------------------------------ --- | --- Module : GHC.IOBase --- Copyright : (c) The University of Glasgow 1994-2009 --- License : see libraries/base/LICENSE >--------------------------------------------------------------- --- Maintainer : [email protected] --- Stability : internal --- Portability : non-portable (GHC Extensions) >--------------------------------------------------------------- --- Backwards-compatibility interface >--------------------------------------------------------------- ------------------------------------------------------------------------------ - -module GHC.IOBase {-# DEPRECATED "use GHC.IO instead" #-} ( - IO(..), unIO, failIO, liftIO, bindIO, thenIO, returnIO, - unsafePerformIO, unsafeInterleaveIO, - unsafeDupablePerformIO, unsafeDupableInterleaveIO, - noDuplicate, - - -- To and from from ST - stToIO, ioToST, unsafeIOToST, unsafeSTToIO, - - -- References - IORef(..), newIORef, readIORef, writeIORef, - IOArray(..), newIOArray, readIOArray, writeIOArray, unsafeReadIOArray, unsafeWriteIOArray, - MVar(..), - - -- Handles, file descriptors, - FilePath, - Handle(..), Handle__(..), HandleType(..), IOMode(..), FD, - isReadableHandleType, isWritableHandleType, isReadWriteHandleType, showHandle, - - -- Buffers - -- Buffer(..), RawBuffer, BufferState(..), - BufferList(..), BufferMode(..), - --bufferIsWritable, bufferEmpty, bufferFull, - - -- Exceptions - Exception(..), ArithException(..), AsyncException(..), ArrayException(..), - stackOverflow, heapOverflow, ioException, - IOError, IOException(..), IOErrorType(..), ioError, userError, - ExitCode(..), - throwIO, block, unblock, blocked, catchAny, catchException, - evaluate, - ErrorCall(..), AssertionFailed(..), assertError, untangle, - BlockedOnDeadMVar(..), BlockedIndefinitely(..), Deadlock(..), - blockedOnDeadMVar, blockedIndefinitely - ) where - -import GHC.Base -import GHC.Exception -import GHC.IO -import GHC.IO.Handle.Types -import GHC.IO.IOMode -import GHC.IO.Exception -import GHC.IOArray -import GHC.IORef -import GHC.MVar -import Foreign.C.Types -import Data.Typeable - -type FD = CInt - --- Backwards compat: this was renamed to BlockedIndefinitelyOnMVar -data BlockedOnDeadMVar = BlockedOnDeadMVar - deriving Typeable - -instance Exception BlockedOnDeadMVar - -instance Show BlockedOnDeadMVar where - showsPrec _ BlockedOnDeadMVar = showString "thread blocked indefinitely" - -blockedOnDeadMVar :: SomeException -- for the RTS -blockedOnDeadMVar = toException BlockedOnDeadMVar - - --- Backwards compat: this was renamed to BlockedIndefinitelyOnSTM -data BlockedIndefinitely = BlockedIndefinitely - deriving Typeable - -instance Exception BlockedIndefinitely - -instance Show BlockedIndefinitely where - showsPrec _ BlockedIndefinitely = showString "thread blocked indefinitely" - -blockedIndefinitely :: SomeException -- for the RTS -blockedIndefinitely = toException BlockedIndefinitely - diff --git a/base.cabal b/base.cabal index 36b8708..752ab63 100644 --- a/base.cabal +++ b/base.cabal @@ -83,7 +83,6 @@ Library { GHC.IO.Handle.Types, GHC.IO.IOMode, GHC.IOArray, - GHC.IOBase, GHC.IORef, GHC.IP, GHC.Int, _______________________________________________ Cvs-libraries mailing list [email protected] http://www.haskell.org/mailman/listinfo/cvs-libraries
