X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FIOBase.lhs;h=233148b0eaffffa011ccb91673cacb6e5820d0c8;hb=28fb12f4e4059674e9396fc76a2783e0ae8798cd;hp=b2ec6e63dae93c4f01458ee58bcc9cf29dc71c45;hpb=90eca6686c8224e7012ee8574890f6e875975e72;p=ghc-base.git diff --git a/GHC/IOBase.lhs b/GHC/IOBase.lhs index b2ec6e6..233148b 100644 --- a/GHC/IOBase.lhs +++ b/GHC/IOBase.lhs @@ -1,5 +1,5 @@ \begin{code} -{-# OPTIONS -fno-implicit-prelude #-} +{-# OPTIONS_GHC -fno-implicit-prelude #-} ----------------------------------------------------------------------------- -- | -- Module : GHC.IOBase @@ -17,6 +17,8 @@ module GHC.IOBase where import GHC.ST +import GHC.Arr -- to derive Ix class +import GHC.Enum -- to derive Enum class import GHC.STRef import GHC.Base import GHC.Num -- To get fromInteger etc, needed because of -fno-implicit-prelude @@ -55,6 +57,19 @@ Libraries - parts of hslibs/lang. --SDM -} +{-| +A value of type @'IO' a@ is a computation which, when performed, +does some I\/O before returning a value of type @a@. + +There is really only one way to \"perform\" an I\/O action: bind it to +@Main.main@ in your program. When your program is run, the I\/O will +be performed. It isn't possible to perform I\/O from an arbitrary +function, unless that function is itself in the 'IO' monad and called +at some point, directly or indirectly, from @Main.main@. + +'IO' is a monad, so 'IO' actions can be combined using either the do-notation +or the '>>' and '>>=' operations from the 'Monad' class. +-} newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #)) unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #)) @@ -97,21 +112,94 @@ returnIO x = IO (\ s -> (# s, x #)) -- --------------------------------------------------------------------------- -- Coercions between IO and ST ---stToIO :: (forall s. ST s a) -> IO a +-- | A monad transformer embedding strict state transformers in the 'IO' +-- monad. The 'RealWorld' parameter indicates that the internal state +-- used by the 'ST' computation is a special one supplied by the 'IO' +-- monad, and thus distinct from those used by invocations of 'runST'. stToIO :: ST RealWorld a -> IO a stToIO (ST m) = IO m ioToST :: IO a -> ST RealWorld a ioToST (IO m) = (ST m) +-- This relies on IO and ST having the same representation modulo the +-- constraint on the type of the state +-- +unsafeIOToST :: IO a -> ST s a +unsafeIOToST (IO io) = ST $ \ s -> (unsafeCoerce# io) s + -- --------------------------------------------------------------------------- -- Unsafe IO operations +{-| +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. + +If the I\/O computation wrapped in 'unsafePerformIO' +performs side effects, then the relative order in which those side +effects take place (relative to the main I\/O trunk, or other calls to +'unsafePerformIO') is indeterminate. You have to be careful when +writing and compiling modules that use 'unsafePerformIO': + + * Use @{\-\# NOINLINE foo \#-\}@ as a pragma on any function @foo@ + that calls 'unsafePerformIO'. If the call is inlined, + the I\/O may be performed more than once. + + * Use the compiler flag @-fno-cse@ to prevent common sub-expression + elimination being performed on the module, which might combine + two side effects that were meant to be separate. A good example + is using multiple global variables (like @test@ in the example below). + + * Make sure that the either you switch off let-floating, or that the + call to 'unsafePerformIO' cannot float outside a lambda. For example, + if you say: + @ + f x = unsafePerformIO (newIORef []) + @ + you may get only one reference cell shared between all calls to @f@. + Better would be + @ + f x = unsafePerformIO (newIORef [x]) + @ + because now it can't float outside the lambda. + +It is less well known that +'unsafePerformIO' is not type safe. For example: + +> test :: IORef [a] +> test = unsafePerformIO $ newIORef [] +> +> main = do +> writeIORef test [42] +> bang <- readIORef test +> print (bang :: [Char]) + +This program will core dump. This problem with polymorphic references +is well known in the ML community, and does not arise with normal +monadic use of references. There is no easy way to make it impossible +once you use 'unsafePerformIO'. Indeed, it is +possible to write @coerce :: a -> b@ with the +help of 'unsafePerformIO'. So be careful! +-} {-# NOINLINE unsafePerformIO #-} unsafePerformIO :: IO a -> a unsafePerformIO (IO m) = case m realWorld# of (# _, r #) -> r -{-# NOINLINE unsafeInterleaveIO #-} +-- Why do we NOINLINE unsafePerformIO? See the comment with +-- GHC.ST.runST. Essentially the issue is that the IO computation +-- inside unsafePerformIO must be atomic: it must either all run, or +-- not at all. If we let the compiler see the application of the IO +-- to realWorld#, it might float out part of the IO. + +{-| +'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 'System.IO.hGetContents'. +-} +{-# INLINE unsafeInterleaveIO #-} unsafeInterleaveIO :: IO a -> IO a unsafeInterleaveIO (IO m) = IO ( \ s -> let @@ -119,6 +207,10 @@ unsafeInterleaveIO (IO m) in (# s, r #)) +-- We believe that INLINE on unsafeInterleaveIO is safe, because the +-- state from this IO thread is passed explicitly to the interleaved +-- IO, so it cannot be floated out and shared. + -- --------------------------------------------------------------------------- -- Handle type @@ -147,11 +239,51 @@ instance Eq (MVar a) where -- Note: when a Handle is garbage collected, we want to flush its buffer -- and close the OS file handle, so as to free up a (precious) resource. +-- | Haskell defines operations to read and write characters from and to files, +-- represented by values of type @Handle@. Each value of this type is a +-- /handle/: a record used by the Haskell run-time system to /manage/ I\/O +-- with file system objects. A handle has at least the following properties: +-- +-- * whether it manages input or output or both; +-- +-- * whether it is /open/, /closed/ or /semi-closed/; +-- +-- * whether the object is seekable; +-- +-- * whether buffering is disabled, or enabled on a line or block basis; +-- +-- * a buffer (whose length may be zero). +-- +-- Most handles will also have a current I\/O position indicating where the next +-- input or output operation will occur. A handle is /readable/ if it +-- manages only input or both input and output; likewise, it is /writable/ if +-- it manages only output or both input and output. A handle is /open/ when +-- first allocated. +-- Once it is closed it can no longer be used for either input or output, +-- though an implementation cannot re-use its storage while references +-- remain to it. Handles are in the 'Show' and 'Eq' classes. The string +-- produced by showing a handle is system dependent; it should include +-- enough information to identify the handle for debugging. A handle is +-- equal according to '==' only to itself; no attempt +-- is made to compare the internal state of different handles for equality. +-- +-- GHC note: a 'Handle' will be automatically closed when the garbage +-- collector detects that it has become unreferenced by the program. +-- However, relying on this behaviour is not generally recommended: +-- the garbage collector is unpredictable. If possible, use explicit +-- an explicit 'hClose' to close 'Handle's when they are no longer +-- required. GHC does not currently attempt to free up file +-- descriptors when they have run out, it is your responsibility to +-- ensure that this doesn't happen. + data Handle = FileHandle -- A normal handle to a file + FilePath -- the file (invariant) !(MVar Handle__) | DuplexHandle -- A handle to a read/write stream + FilePath -- file for a FIFO, otherwise some + -- descriptive string. !(MVar Handle__) -- The read side !(MVar Handle__) -- The write side @@ -160,8 +292,8 @@ data Handle -- seekable. instance Eq Handle where - (FileHandle h1) == (FileHandle h2) = h1 == h2 - (DuplexHandle h1 _) == (DuplexHandle h2 _) = h1 == h2 + (FileHandle _ h1) == (FileHandle _ h2) = h1 == h2 + (DuplexHandle _ h1 _) == (DuplexHandle _ h2 _) = h1 == h2 _ == _ = False type FD = Int -- XXX ToDo: should be CInt @@ -173,7 +305,6 @@ data Handle__ haIsBin :: Bool, -- binary mode? haIsStream :: Bool, -- is this a stream handle? haBufferMode :: BufferMode, -- buffer contains read/write data? - haFilePath :: FilePath, -- file name, possibly haBuffer :: !(IORef Buffer), -- the current buffer haBuffers :: !(IORef BufferList), -- spare buffers haOtherSide :: Maybe (MVar Handle__) -- ptr to the write side of a @@ -265,70 +396,128 @@ isWritableHandleType WriteHandle = True isWritableHandleType ReadWriteHandle = True isWritableHandleType _ = False --- File names are specified using @FilePath@, a OS-dependent --- string that (hopefully, I guess) maps to an accessible file/object. +-- | File and directory names are values of type 'String', whose precise +-- meaning is operating system dependent. Files can be opened, yielding a +-- handle which can then be used to operate on the contents of that file. type FilePath = String -- --------------------------------------------------------------------------- -- Buffering modes --- Three kinds of buffering are supported: line-buffering, +-- | Three kinds of buffering are supported: line-buffering, -- block-buffering or no-buffering. These modes have the following --- effects. For output, items are written out from the internal --- buffer according to the buffer mode: +-- effects. For output, items are written out, or /flushed/, +-- from the internal buffer according to the buffer mode: -- --- o line-buffering the entire output buffer is written --- out whenever a newline is output, the output buffer overflows, --- a flush is issued, or the handle is closed. +-- * /line-buffering/: the entire output buffer is flushed +-- whenever a newline is output, the buffer overflows, +-- a 'System.IO.hFlush' is issued, or the handle is closed. -- --- o block-buffering the entire output buffer is written out whenever --- it overflows, a flush is issued, or the handle --- is closed. +-- * /block-buffering/: the entire buffer is written out whenever it +-- overflows, a 'System.IO.hFlush' is issued, or the handle is closed. -- --- o no-buffering output is written immediately, and never stored --- in the output buffer. +-- * /no-buffering/: output is written immediately, and never stored +-- in the buffer. -- +-- An implementation is free to flush the buffer more frequently, +-- but not less frequently, than specified above. -- The output buffer is emptied as soon as it has been written out. - --- Similarly, input occurs according to the buffer mode for handle {\em hdl}. - --- o line-buffering when the input buffer for the handle is not empty, --- the next item is obtained from the buffer; --- otherwise, when the input buffer is empty, --- characters up to and including the next newline --- character are read into the buffer. No characters --- are available until the newline character is --- available. -- --- o block-buffering when the input buffer for the handle becomes empty, --- the next block of data is read into this buffer. +-- Similarly, input occurs according to the buffer mode for the handle: -- --- o no-buffering the next input item is read and returned. - +-- * /line-buffering/: when the buffer for the handle is not empty, +-- the next item is obtained from the buffer; otherwise, when the +-- buffer is empty, characters up to and including the next newline +-- character are read into the buffer. No characters are available +-- until the newline character is available or the buffer is full. +-- +-- * /block-buffering/: when the buffer for the handle becomes empty, +-- the next block of data is read into the buffer. +-- +-- * /no-buffering/: the next input item is read and returned. +-- The 'System.IO.hLookAhead' operation implies that even a no-buffered +-- handle may require a one-character buffer. +-- +-- The default buffering mode when a handle is opened is +-- implementation-dependent and may depend on the file system object +-- which is attached to that handle. -- For most implementations, physical files will normally be block-buffered --- and terminals will normally be line-buffered. (the IO interface provides --- operations for changing the default buffering of a handle tho.) +-- and terminals will normally be line-buffered. data BufferMode - = NoBuffering | LineBuffering | BlockBuffering (Maybe Int) + = NoBuffering -- ^ buffering is disabled if possible. + | LineBuffering + -- ^ line-buffering should be enabled if possible. + | BlockBuffering (Maybe Int) + -- ^ block-buffering should be enabled if possible. + -- The size of the buffer is @n@ items if the argument + -- is 'Just' @n@ and is otherwise implementation-dependent. deriving (Eq, Ord, Read, Show) -- --------------------------------------------------------------------------- -- IORefs -newtype IORef a = IORef (STRef RealWorld a) deriving Eq +-- |A mutable variable in the 'IO' monad +newtype IORef a = IORef (STRef RealWorld a) + +-- explicit instance because Haddock can't figure out a derived one +instance Eq (IORef a) where + IORef x == IORef y = x == y +-- |Build a new 'IORef' newIORef :: a -> IO (IORef a) newIORef v = stToIO (newSTRef v) >>= \ var -> return (IORef var) +-- |Read the value of an 'IORef' readIORef :: IORef a -> IO a readIORef (IORef var) = stToIO (readSTRef var) +-- |Write a new value into an 'IORef' 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) + +-- explicit instance because Haddock can't figure out a derived one +instance Eq (IOArray i e) where + IOArray x == IOArray y = x == y + +-- |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 @@ -346,68 +535,97 @@ instance Show HandleType where ReadWriteHandle -> showString "read-writable" instance Show Handle where - showsPrec p (FileHandle h) = showHandle p h False - showsPrec p (DuplexHandle _ h) = showHandle p h True - -showHandle p h duplex = - let - -- (Big) SIGH: unfolded defn of takeMVar to avoid - -- an (oh-so) unfortunate module loop with GHC.Conc. - hdl_ = unsafePerformIO (IO $ \ s# -> - case h of { MVar h# -> - case takeMVar# h# s# of { (# s2# , r #) -> - case putMVar# h# r s2# of { s3# -> - (# s3#, r #) }}}) - - showType | duplex = showString "duplex (read-write)" - | otherwise = showsPrec p (haType hdl_) - in - showChar '{' . - showHdl (haType hdl_) - (showString "loc=" . showString (haFilePath hdl_) . showChar ',' . - showString "type=" . showType . showChar ',' . - showString "binary=" . showsPrec p (haIsBin hdl_) . showChar ',' . - showString "buffering=" . showBufMode (unsafePerformIO (readIORef (haBuffer hdl_))) (haBufferMode hdl_) . showString "}" ) - where - - showHdl :: HandleType -> ShowS -> ShowS - showHdl ht cont = - case ht of - ClosedHandle -> showsPrec p ht . showString "}" - _ -> cont - - showBufMode :: Buffer -> BufferMode -> ShowS - showBufMode buf bmo = - case bmo of - NoBuffering -> showString "none" - LineBuffering -> showString "line" - BlockBuffering (Just n) -> showString "block " . showParen True (showsPrec p n) - BlockBuffering Nothing -> showString "block " . showParen True (showsPrec p def) - where - def :: Int - def = bufSize buf + showsPrec p (FileHandle file _) = showHandle file + showsPrec p (DuplexHandle file _ _) = showHandle file + +showHandle file = showString "{handle: " . showString file . showString "}" -- ------------------------------------------------------------------------ -- Exception datatype and operations +-- |The type of exceptions. Every kind of system-generated exception +-- has a constructor in the 'Exception' type, and values of other +-- types may be injected into 'Exception' by coercing them to +-- 'Data.Dynamic.Dynamic' (see the section on Dynamic Exceptions: +-- "Control.Exception\#DynamicExceptions"). data Exception - = IOException IOException -- IO exceptions - | ArithException ArithException -- Arithmetic exceptions - | ArrayException ArrayException -- Array-related exceptions - | ErrorCall String -- Calls to 'error' - | ExitException ExitCode -- Call to System.exitWith - | NoMethodError String -- A non-existent method was invoked - | PatternMatchFail String -- A pattern match / guard failure - | RecSelError String -- Selecting a non-existent field - | RecConError String -- Field missing in record construction - | RecUpdError String -- Record doesn't contain updated field - | AssertionFailed String -- Assertions - | DynException Dynamic -- Dynamic exceptions - | AsyncException AsyncException -- Externally generated errors - | BlockedOnDeadMVar -- Blocking on a dead MVar - | Deadlock -- no threads can run (raised in main thread) + = ArithException ArithException + -- ^Exceptions raised by arithmetic + -- operations. (NOTE: GHC currently does not throw + -- 'ArithException's except for 'DivideByZero'). + | ArrayException ArrayException + -- ^Exceptions raised by array-related + -- operations. (NOTE: GHC currently does not throw + -- 'ArrayException's). + | AssertionFailed String + -- ^This exception is thrown by the + -- 'assert' operation when the condition + -- fails. The 'String' argument contains the + -- location of the assertion in the source program. + | AsyncException AsyncException + -- ^Asynchronous exceptions (see section on Asynchronous Exceptions: "Control.Exception\#AsynchronousExceptions"). + | BlockedOnDeadMVar + -- ^The current thread was executing a call to + -- 'Control.Concurrent.MVar.takeMVar' that could never return, + -- because there are no other references to this 'MVar'. + | BlockedIndefinitely + -- ^The current thread was waiting to retry an atomic memory transaction + -- that could never become possible to complete because there are no other + -- threads referring to any of teh TVars involved. + | Deadlock + -- ^There are no runnable threads, so the program is + -- deadlocked. The 'Deadlock' exception is + -- raised in the main thread only (see also: "Control.Concurrent"). + | DynException Dynamic + -- ^Dynamically typed exceptions (see section on Dynamic Exceptions: "Control.Exception\#DynamicExceptions"). + | ErrorCall String + -- ^The 'ErrorCall' exception is thrown by 'error'. The 'String' + -- argument of 'ErrorCall' is the string passed to 'error' when it was + -- called. + | ExitException ExitCode + -- ^The 'ExitException' exception is thrown by 'System.Exit.exitWith' (and + -- 'System.Exit.exitFailure'). The 'ExitCode' argument is the value passed + -- to 'System.Exit.exitWith'. An unhandled 'ExitException' exception in the + -- main thread will cause the program to be terminated with the given + -- exit code. + | IOException IOException + -- ^These are the standard IO exceptions generated by + -- Haskell\'s @IO@ operations. See also "System.IO.Error". + | NoMethodError String + -- ^An attempt was made to invoke a class method which has + -- no definition in this instance, and there was no default + -- definition given in the class declaration. GHC issues a + -- warning when you compile an instance which has missing + -- methods. | NonTermination - + -- ^The current thread is stuck in an infinite loop. This + -- exception may or may not be thrown when the program is + -- non-terminating. + | PatternMatchFail String + -- ^A pattern matching failure. The 'String' argument should contain a + -- descriptive message including the function name, source file + -- and line number. + | RecConError String + -- ^An attempt was made to evaluate a field of a record + -- for which no value was given at construction time. The + -- 'String' argument gives the location of the + -- record construction in the source program. + | RecSelError String + -- ^A field selection was attempted on a constructor that + -- doesn\'t have the requested field. This can happen with + -- multi-constructor records when one or more fields are + -- missing from some of the constructors. The + -- 'String' argument gives the location of the + -- record selection in the source program. + | RecUpdError String + -- ^An attempt was made to update a field in a record, + -- where the record doesn\'t have the requested field. This can + -- only occur with multi-constructor records, when one or more + -- fields are missing from some of the constructors. The + -- 'String' argument gives the location of the + -- record update in the source program. + +-- |The type of arithmetic exceptions data ArithException = Overflow | Underflow @@ -416,15 +634,38 @@ data ArithException | Denormal deriving (Eq, Ord) + +-- |Asynchronous exceptions data AsyncException = StackOverflow + -- ^The current thread\'s stack exceeded its limit. + -- Since an exception has been raised, the thread\'s stack + -- will certainly be below its limit again, but the + -- programmer should take remedial action + -- immediately. | HeapOverflow + -- ^The program\'s heap is reaching its limit, and + -- the program should take action to reduce the amount of + -- live data it has. Notes: + -- + -- * It is undefined which thread receives this exception. + -- + -- * GHC currently does not throw 'HeapOverflow' exceptions. | ThreadKilled + -- ^This exception is raised by another thread + -- calling 'Control.Concurrent.killThread', or by the system + -- if it needs to terminate the thread for some + -- reason. deriving (Eq, Ord) +-- | Exceptions generated by array operations data ArrayException - = IndexOutOfBounds String -- out-of-range array access - | UndefinedElement String -- evaluating an undefined element + = IndexOutOfBounds String + -- ^An attempt was made to index an array outside + -- its declared bounds. + | UndefinedElement String + -- ^An attempt was made to evaluate an element of an + -- array that had not been initialized. deriving (Eq, Ord) stackOverflow, heapOverflow :: Exception -- for the RTS @@ -468,6 +709,7 @@ instance Show Exception where showsPrec _ (DynException _err) = showString "unknown exception" showsPrec _ (AsyncException e) = shows e showsPrec _ (BlockedOnDeadMVar) = showString "thread blocked indefinitely" + showsPrec _ (BlockedIndefinitely) = showString "thread blocked indefinitely" showsPrec _ (NonTermination) = showString "<>" showsPrec _ (Deadlock) = showString "<>" @@ -488,52 +730,78 @@ instance Eq Exception where BlockedOnDeadMVar == BlockedOnDeadMVar = True NonTermination == NonTermination = True Deadlock == Deadlock = True + _ == _ = False -- ----------------------------------------------------------------------------- -- The ExitCode type --- The `ExitCode' type defines the exit codes that a program --- can return. `ExitSuccess' indicates successful termination; --- and `ExitFailure code' indicates program failure --- with value `code'. The exact interpretation of `code' --- is operating-system dependent. In particular, some values of --- `code' may be prohibited (e.g. 0 on a POSIX-compliant system). - -- We need it here because it is used in ExitException in the -- Exception datatype (above). -data ExitCode = ExitSuccess | ExitFailure Int - deriving (Eq, Ord, Read, Show) +data ExitCode + = ExitSuccess -- ^ indicates successful termination; + | ExitFailure Int + -- ^ indicates program failure with an exit code. + -- The exact interpretation of the code is + -- operating-system dependent. In particular, some values + -- may be prohibited (e.g. 0 on a POSIX-compliant system). + deriving (Eq, Ord, Read, Show) -- -------------------------------------------------------------------------- -- Primitive throw +-- | Throw an exception. Exceptions may be thrown from purely +-- functional code, but may only be caught within the 'IO' monad. throw :: Exception -> a throw exception = raise# exception -ioError :: Exception -> IO a -ioError err = IO $ \s -> throw err s +-- | A variant of 'throw' that can be used within the 'IO' monad. +-- +-- 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 +-- > throwIO e `seq` return () ===> return () +-- +-- The first example will cause the exception @e@ to be raised, +-- 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 '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. +throwIO :: Exception -> IO a +throwIO err = IO $ raiseIO# err ioException :: IOException -> IO a -ioException err = IO $ \s -> throw (IOException err) s +ioException err = IO $ raiseIO# (IOException err) + +-- | Raise an 'IOError' in the 'IO' monad. +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. +-- Any I\/O operation may raise an 'IOError' instead of returning a result. +-- For a more general type of exception, including also those that arise +-- in pure code, see 'Control.Exception.Exception'. +-- +-- 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. } @@ -541,6 +809,7 @@ instance Eq IOException where (IOError h1 e1 loc1 str1 fn1) == (IOError h2 e2 loc2 str2 fn2) = e1==e2 && str1==str2 && h1==h2 && loc1==loc2 && fn1==fn2 +-- | An abstract type that contains a value for each variant of 'IOError'. data IOErrorType -- Haskell 98: = AlreadyExists @@ -569,7 +838,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 = @@ -596,25 +865,38 @@ instance Show IOErrorType where UnsupportedOperation -> "unsupported operation" DynIOError{} -> "unknown IO error" +-- | Construct an 'IOError' value with a string describing the error. +-- The 'fail' method of the 'IO' instance of the 'Monad' class raises a +-- 'userError', thus: +-- +-- > instance Monad IO where +-- > ... +-- > fail s = ioError (userError s) +-- userError :: String -> IOError -userError str = IOException (IOError Nothing UserError "" str Nothing) +userError str = IOError Nothing UserError "" str Nothing -- --------------------------------------------------------------------------- -- Showing IOErrors instance Show IOException where showsPrec p (IOError hdl iot loc s fn) = - showsPrec p iot . + (case fn of + Nothing -> case hdl of + Nothing -> id + Just h -> showsPrec p h . showString ": " + Just name -> showString name . showString ": ") . (case loc of "" -> id - _ -> showString "\nAction: " . showString loc) . - (case hdl of - Nothing -> id - Just h -> showString "\nHandle: " . showsPrec p h) . + _ -> showString loc . showString ": ") . + showsPrec p iot . (case s of "" -> id - _ -> showString "\nReason: " . showString s) . - (case fn of - Nothing -> id - Just name -> showString "\nFile: " . showString name) + _ -> showString " (" . showString s . showString ")") + +-- ----------------------------------------------------------------------------- +-- IOMode type + +data IOMode = ReadMode | WriteMode | AppendMode | ReadWriteMode + deriving (Eq, Ord, Ix, Enum, Read, Show) \end{code}