[project @ 2003-04-17 15:23:37 by simonpj]
[ghc-base.git] / GHC / IOBase.lhs
index 6f7d9c9..cf3c5eb 100644 (file)
@@ -123,7 +123,7 @@ ioToST (IO m) = (ST m)
 -- Unsafe IO operations
 
 {-|
-This is the "back door" into the 'IO' monad, allowing
+This is the \"back door\" into the 'IO' monad, allowing
 'IO' computation to be performed at any time.  For
 this to be safe, the 'IO' computation should be
 free of side effects and independent of its environment.
@@ -182,7 +182,7 @@ unsafePerformIO (IO m) = case m realWorld# of (# _, r #)   -> r
 'unsafeInterleaveIO' allows 'IO' computation to be deferred lazily.
 When passed a value of type @IO a@, the 'IO' will only be performed
 when the value of the @a@ is demanded.  This is used to implement lazy
-file reading, see 'IO.hGetContents'.
+file reading, see 'System.IO.hGetContents'.
 -}
 {-# NOINLINE unsafeInterleaveIO #-}
 unsafeInterleaveIO :: IO a -> IO a
@@ -406,6 +406,42 @@ writeIORef  :: IORef a -> a -> IO ()
 writeIORef (IORef var) v = stToIO (writeSTRef var v)
 
 -- ---------------------------------------------------------------------------
+-- | An 'IOArray' is a mutable, boxed, non-strict array in the 'IO' monad.  
+-- The type arguments are as follows:
+--
+--  * @i@: the index type of the array (should be an instance of @Ix@)
+--
+--  * @e@: the element type of the array.
+--
+-- 
+
+newtype IOArray i e = IOArray (STArray RealWorld i e) deriving Eq
+
+-- |Build a new 'IOArray'
+newIOArray :: Ix i => (i,i) -> e -> IO (IOArray i e)
+{-# INLINE newIOArray #-}
+newIOArray lu init  = stToIO $ do {marr <- newSTArray lu init; return (IOArray marr)}
+
+-- | Read a value from an 'IOArray'
+unsafeReadIOArray  :: Ix i => IOArray i e -> Int -> IO e
+{-# INLINE unsafeReadIOArray #-}
+unsafeReadIOArray (IOArray marr) i = stToIO (unsafeReadSTArray marr i)
+
+-- | Write a new value into an 'IOArray'
+unsafeWriteIOArray :: Ix i => IOArray i e -> Int -> e -> IO ()
+{-# INLINE unsafeWriteIOArray #-}
+unsafeWriteIOArray (IOArray marr) i e = stToIO (unsafeWriteSTArray marr i e)
+
+-- | Read a value from an 'IOArray'
+readIOArray  :: Ix i => IOArray i e -> i -> IO e
+readIOArray (IOArray marr) i = stToIO (readSTArray marr i)
+
+-- | Write a new value into an 'IOArray'
+writeIOArray :: Ix i => IOArray i e -> i -> e -> IO ()
+writeIOArray (IOArray marr) i e = stToIO (writeSTArray marr i e)
+
+
+-- ---------------------------------------------------------------------------
 -- Show instance for Handles
 
 -- handle types are 'show'n when printing error msgs, so
@@ -471,14 +507,11 @@ showHandle p h duplex =
 -- has a constructor in the 'Exception' type, and values of other
 -- types may be injected into 'Exception' by coercing them to
 -- 'Dynamic' (see the section on Dynamic Exceptions: "Control.Exception\#DynamicExceptions").
---
--- For backwards compatibility with Haskell 98, 'IOError' is a type synonym
--- for 'Exception'.
 data Exception
   = ArithException     ArithException
        -- ^Exceptions raised by arithmetic
        -- operations.  (NOTE: GHC currently does not throw
-       -- 'ArithException's).
+       -- 'ArithException's except for 'DivideByZero').
   | ArrayException     ArrayException
        -- ^Exceptions raised by array-related
        -- operations.  (NOTE: GHC currently does not throw
@@ -651,6 +684,7 @@ instance Eq Exception where
   BlockedOnDeadMVar   == BlockedOnDeadMVar   = True
   NonTermination      == NonTermination      = True
   Deadlock            == Deadlock            = True
+  _                   == _                   = False
 
 -- -----------------------------------------------------------------------------
 -- The ExitCode type
@@ -678,42 +712,46 @@ throw exception = raise# exception
 
 -- | A variant of 'throw' that can be used within the 'IO' monad.
 --
--- Although 'ioError' has a type that is an instance of the type of 'throw', the
+-- Although 'throwIO' has a type that is an instance of the type of 'throw', the
 -- two functions are subtly different:
 --
 -- > throw e   `seq` return ()  ===> throw e
--- > ioError e `seq` return ()  ===> return ()
+-- > throwIO e `seq` return ()  ===> return ()
 --
 -- The first example will cause the exception @e@ to be raised,
--- whereas the second one won\'t.  In fact, 'ioError' will only cause
+-- whereas the second one won\'t.  In fact, 'throwIO' will only cause
 -- an exception to be raised when it is used within the 'IO' monad.
--- The 'ioError' variant should be used in preference to 'throw' to
+-- The 'throwIO' variant should be used in preference to 'throw' to
 -- raise an exception within the 'IO' monad because it guarantees
 -- ordering with respect to other 'IO' operations, whereas 'throw'
 -- does not.
-ioError         :: Exception -> IO a 
-ioError err    =  IO $ \s -> throw err s
+throwIO         :: Exception -> IO a 
+throwIO err    =  IO $ \s -> throw err s
 
 ioException    :: IOException -> IO a
 ioException err =  IO $ \s -> throw (IOException err) s
 
+ioError         :: IOError -> IO a 
+ioError                =  ioException
+
 -- ---------------------------------------------------------------------------
 -- IOError type
 
--- A value @IOError@ encode errors occurred in the @IO@ monad.
--- An @IOError@ records a more specific error type, a descriptive
+-- | The Haskell 98 type for exceptions in the @IO@ monad.
+-- In Haskell 98, this is an opaque type.
+type IOError = IOException
+
+-- |Exceptions that occur in the @IO@ monad.
+-- An @IOException@ records a more specific error type, a descriptive
 -- string and maybe the handle that was used when the error was
 -- flagged.
-
-type IOError = Exception
-
 data IOException
  = IOError {
      ioe_handle   :: Maybe Handle,   -- the handle used by the action flagging 
                                     -- the error.
      ioe_type     :: IOErrorType,    -- what it was.
      ioe_location :: String,        -- location.
-     ioe_descr    :: String,         -- error type specific information.
+     ioe_description :: String,      -- error type specific information.
      ioe_filename :: Maybe FilePath  -- filename the error is related to.
    }
 
@@ -749,7 +787,7 @@ instance Eq IOErrorType where
    x == y = 
      case x of
        DynIOError{} -> False -- from a strictness POV, compatible with a derived Eq inst?
-       _ -> getTag# x ==# getTag# y
+       _ -> getTag x ==# getTag y
  
 instance Show IOErrorType where
   showsPrec _ e =
@@ -777,7 +815,7 @@ instance Show IOErrorType where
       DynIOError{}      -> "unknown IO error"
 
 userError       :: String  -> IOError
-userError str  =  IOException (IOError Nothing UserError "" str Nothing)
+userError str  =  IOError Nothing UserError "" str Nothing
 
 -- ---------------------------------------------------------------------------
 -- Showing IOErrors