X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FIOBase.lhs;h=60ae45b0a28f304a641b0257f324f440c6821d0e;hb=3aca3f915d2edc71a8633181577258f04996e42a;hp=e7f5bd0c4f2f17b9e49fb6a30eb8b06c39ccb9d6;hpb=7de50399a42ee49b0473b7b6eea2b44a2f941a12;p=ghc-base.git diff --git a/GHC/IOBase.lhs b/GHC/IOBase.lhs index e7f5bd0..60ae45b 100644 --- a/GHC/IOBase.lhs +++ b/GHC/IOBase.lhs @@ -1,18 +1,24 @@ -% ------------------------------------------------------------------------------ -% $Id: IOBase.lhs,v 1.6 2002/02/05 17:32:26 simonmar Exp $ -% -% (c) The University of Glasgow, 1994-2001 -% - -% Definitions for the @IO@ monad and its friends. Everything is exported -% concretely; the @IO@ module itself exports abstractly. - \begin{code} {-# OPTIONS -fno-implicit-prelude #-} +----------------------------------------------------------------------------- +-- | +-- Module : GHC.IOBase +-- Copyright : (c) The University of Glasgow 1994-2002 +-- License : see libraries/base/LICENSE +-- +-- Maintainer : cvs-ghc@haskell.org +-- Stability : internal +-- Portability : non-portable (GHC Extensions) +-- +-- Definitions for the 'IO' monad and its friends. +-- +----------------------------------------------------------------------------- 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 @@ -20,7 +26,10 @@ import Data.Maybe ( Maybe(..) ) import GHC.Show import GHC.List import GHC.Read -import GHC.Dynamic + +#ifndef __HADDOCK__ +import {-# SOURCE #-} Data.Dynamic +#endif -- --------------------------------------------------------------------------- -- The IO Monad @@ -48,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 #)) @@ -78,6 +100,12 @@ bindIO (IO m) k = IO ( \ s -> (# new_s, a #) -> unIO (k a) new_s ) +thenIO :: IO a -> IO b -> IO b +thenIO (IO m) k = IO ( \ s -> + case m s of + (# new_s, a #) -> unIO k new_s + ) + returnIO :: a -> IO a returnIO x = IO (\ s -> (# s, x #)) @@ -94,10 +122,67 @@ ioToST (IO m) = (ST m) -- --------------------------------------------------------------------------- -- 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 +{-| +'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'. +-} {-# NOINLINE unsafeInterleaveIO #-} unsafeInterleaveIO :: IO a -> IO a unsafeInterleaveIO (IO m) @@ -110,6 +195,11 @@ unsafeInterleaveIO (IO m) -- Handle type data MVar a = MVar (MVar# RealWorld a) +{- ^ +An 'MVar' (pronounced \"em-var\") is a synchronising variable, used +for communication between concurrent threads. It can be thought of +as a a box, which may be empty or full. +-} -- pull in Eq (Mvar a) too, to avoid GHC.Conc being an orphan-instance module instance Eq (MVar a) where @@ -260,22 +350,22 @@ type FilePath = String -- effects. For output, items are written out from the internal -- buffer according to the buffer mode: -- --- * line-buffering the entire output buffer is written +-- 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. -- --- * block-buffering the entire output buffer is written out whenever +-- o block-buffering the entire output buffer is written out whenever -- it overflows, a flush is issued, or the handle -- is closed. -- --- * no-buffering output is written immediately, and never stored +-- o no-buffering output is written immediately, and never stored -- in the output buffer. -- -- 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}. --- * line-buffering when the input buffer for the handle is not empty, +-- 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 @@ -283,10 +373,10 @@ type FilePath = String -- are available until the newline character is -- available. -- --- * block-buffering when the input buffer for the handle becomes empty, +-- o block-buffering when the input buffer for the handle becomes empty, -- the next block of data is read into this buffer. -- --- * no-buffering the next input item is read and returned. +-- o no-buffering the next input item is read and returned. -- For most implementations, physical files will normally be block-buffered -- and terminals will normally be line-buffered. (the IO interface provides @@ -299,14 +389,18 @@ data BufferMode -- --------------------------------------------------------------------------- -- IORefs +-- |A mutable variable in the 'IO' monad newtype IORef a = IORef (STRef RealWorld a) deriving Eq +-- |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) @@ -372,24 +466,87 @@ showHandle p h duplex = -- ------------------------------------------------------------------------ -- 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 +-- '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 - = 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). + | 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 + -- 'takeMVar' that could never return, because there are no other + -- references to this 'MVar'. + | 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.exitWith' (and + -- 'System.exitFailure'). The 'ExitCode' argument is the value passed + -- to 'System.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 @@ -398,15 +555,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 '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 @@ -490,9 +670,26 @@ data ExitCode = ExitSuccess | ExitFailure Int -- -------------------------------------------------------------------------- -- 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 +-- | 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 +-- two functions are subtly different: +-- +-- > throw e `seq` return () ===> throw e +-- > ioError 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 +-- an exception to be raised when it is used within the 'IO' monad. +-- The 'ioError' 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 @@ -599,4 +796,10 @@ instance Show IOException where (case fn of Nothing -> id Just name -> showString "\nFile: " . showString name) + +-- ----------------------------------------------------------------------------- +-- IOMode type + +data IOMode = ReadMode | WriteMode | AppendMode | ReadWriteMode + deriving (Eq, Ord, Ix, Enum, Read, Show) \end{code}