Haskell Core Libraries (base package)ParentContentsIndex
GHC.IOBase
Portability non-portable (GHC Extensions)
Stability internal
Maintainer cvs-ghc@haskell.org
Description
Definitions for the IO monad and its friends.
Synopsis
newtype IO a = IO (State# RealWorld -> (#State# RealWorld, a#))
unIO :: IO a -> State# RealWorld -> (#State# RealWorld, a#)
failIO :: String -> IO a
liftIO :: IO a -> State# RealWorld -> STret RealWorld a
bindIO :: IO a -> (a -> IO b) -> IO b
thenIO :: IO a -> IO b -> IO b
returnIO :: a -> IO a
stToIO :: ST RealWorld a -> IO a
ioToST :: IO a -> ST RealWorld a
unsafePerformIO :: IO a -> a
unsafeInterleaveIO :: IO a -> IO a
data MVar a = MVar (MVar# RealWorld a)
data Handle
= FileHandle !(MVar Handle__)
| DuplexHandle !(MVar Handle__) !(MVar Handle__)
type FD = Int
data Handle__ = Handle__ {
haFD :: !FD
haType :: HandleType
haIsBin :: Bool
haIsStream :: Bool
haBufferMode :: BufferMode
haFilePath :: FilePath
haBuffer :: !(IORef Buffer)
haBuffers :: !(IORef BufferList)
haOtherSide :: (Maybe (MVar Handle__))
}
type RawBuffer = MutableByteArray# RealWorld
data Buffer = Buffer {
bufBuf :: RawBuffer
bufRPtr :: !Int
bufWPtr :: !Int
bufSize :: !Int
bufState :: BufferState
}
data BufferState
= ReadBuffer
| WriteBuffer
data BufferList
= BufferListNil
| BufferListCons RawBuffer BufferList
bufferIsWritable :: Buffer -> Bool
bufferEmpty :: Buffer -> Bool
bufferFull :: Buffer -> Bool
data HandleType
= ClosedHandle
| SemiClosedHandle
| ReadHandle
| WriteHandle
| AppendHandle
| ReadWriteHandle
type FilePath = String
data BufferMode
= NoBuffering
| LineBuffering
| BlockBuffering (Maybe Int)
newtype IORef a = IORef (STRef RealWorld a)
newIORef :: a -> IO (IORef a)
readIORef :: IORef a -> IO a
writeIORef :: IORef a -> a -> IO ()
newtype IOArray i e = IOArray (STArray RealWorld i e)
newIOArray :: (Ix i) => (i, i) -> e -> IO (IOArray i e)
unsafeReadIOArray :: (Ix i) => IOArray i e -> Int -> IO e
unsafeWriteIOArray :: (Ix i) => IOArray i e -> Int -> e -> IO ()
readIOArray :: (Ix i) => IOArray i e -> i -> IO e
writeIOArray :: (Ix i) => IOArray i e -> i -> e -> IO ()
data Exception
= ArithException ArithException
| ArrayException ArrayException
| AssertionFailed String
| AsyncException AsyncException
| BlockedOnDeadMVar
| Deadlock
| DynException Dynamic
| ErrorCall String
| ExitException ExitCode
| IOException IOException
| NoMethodError String
| NonTermination
| PatternMatchFail String
| RecConError String
| RecSelError String
| RecUpdError String
data ArithException
= Overflow
| Underflow
| LossOfPrecision
| DivideByZero
| Denormal
data AsyncException
= StackOverflow
| HeapOverflow
| ThreadKilled
data ArrayException
= IndexOutOfBounds String
| UndefinedElement String
stackOverflow :: Exception
heapOverflow :: Exception
data ExitCode
= ExitSuccess
| ExitFailure Int
throw :: Exception -> a
throwIO :: Exception -> IO a
ioException :: IOException -> IO a
ioError :: IOError -> IO a
type IOError = IOException
data IOException = IOError {
ioe_handle :: (Maybe Handle)
ioe_type :: IOErrorType
ioe_location :: String
ioe_description :: String
ioe_filename :: (Maybe FilePath)
}
data IOErrorType
= AlreadyExists
| NoSuchThing
| ResourceBusy
| ResourceExhausted
| EOF
| IllegalOperation
| PermissionDenied
| UserError
| UnsatisfiedConstraints
| SystemError
| ProtocolError
| OtherError
| InvalidArgument
| InappropriateType
| HardwareFault
| UnsupportedOperation
| TimeExpired
| ResourceVanished
| Interrupted
| DynIOError Dynamic
userError :: String -> IOError
data IOMode
= ReadMode
| WriteMode
| AppendMode
| ReadWriteMode
Documentation
newtype IO a

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.

Constructors
IO (State# RealWorld -> (#State# RealWorld, a#))
Instances
MonadPlus IO
MonadError IOError IO
MonadFix IO
MonadIO IO
MArray IOArray e IO
MArray IOUArray Bool IO
MArray IOUArray Char IO
MArray IOUArray Int IO
MArray IOUArray Word IO
MArray IOUArray (Ptr a) IO
MArray IOUArray (FunPtr a) IO
MArray IOUArray Float IO
MArray IOUArray Double IO
MArray IOUArray (StablePtr a) IO
MArray IOUArray Int8 IO
MArray IOUArray Int16 IO
MArray IOUArray Int32 IO
MArray IOUArray Int64 IO
MArray IOUArray Word8 IO
MArray IOUArray Word16 IO
MArray IOUArray Word32 IO
MArray IOUArray Word64 IO
(Storable e) => MArray StorableArray e IO
(Typeable a) => Typeable (IO a)
Functor IO
Monad IO
unIO :: IO a -> State# RealWorld -> (#State# RealWorld, a#)
failIO :: String -> IO a
liftIO :: IO a -> State# RealWorld -> STret RealWorld a
bindIO :: IO a -> (a -> IO b) -> IO b
thenIO :: IO a -> IO b -> IO b
returnIO :: a -> IO a
stToIO :: ST RealWorld a -> IO a
ioToST :: IO a -> ST RealWorld a
unsafePerformIO :: IO a -> a

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!

unsafeInterleaveIO :: IO a -> IO a
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 hGetContents.
data MVar 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.
Constructors
MVar (MVar# RealWorld a)
Instances
Eq (MVar a)
data Handle
Constructors
FileHandle !(MVar Handle__)
DuplexHandle !(MVar Handle__) !(MVar Handle__)
Instances
Typeable Handle
Eq Handle
Show Handle
type FD = Int
data Handle__
Constructors
Handle__
haFD :: !FD
haType :: HandleType
haIsBin :: Bool
haIsStream :: Bool
haBufferMode :: BufferMode
haFilePath :: FilePath
haBuffer :: !(IORef Buffer)
haBuffers :: !(IORef BufferList)
haOtherSide :: (Maybe (MVar Handle__))
type RawBuffer = MutableByteArray# RealWorld
data Buffer
Constructors
Buffer
bufBuf :: RawBuffer
bufRPtr :: !Int
bufWPtr :: !Int
bufSize :: !Int
bufState :: BufferState
data BufferState
Constructors
ReadBuffer
WriteBuffer
Instances
Eq BufferState
data BufferList
Constructors
BufferListNil
BufferListCons RawBuffer BufferList
bufferIsWritable :: Buffer -> Bool
bufferEmpty :: Buffer -> Bool
bufferFull :: Buffer -> Bool
data HandleType
Constructors
ClosedHandle
SemiClosedHandle
ReadHandle
WriteHandle
AppendHandle
ReadWriteHandle
Instances
Show HandleType
type FilePath = String
data BufferMode
Constructors
NoBuffering
LineBuffering
BlockBuffering (Maybe Int)
Instances
Eq BufferMode
Ord BufferMode
Read BufferMode
Show BufferMode
newtype IORef a
A mutable variable in the IO monad
Constructors
IORef (STRef RealWorld a)
Instances
(Typeable a) => Typeable (IORef a)
Eq (IORef a)
newIORef :: a -> IO (IORef a)
Build a new IORef
readIORef :: IORef a -> IO a
Read the value of an IORef
writeIORef :: IORef a -> a -> IO ()
Write a new value into an IORef
newtype IOArray i e

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.

Constructors
IOArray (STArray RealWorld i e)
Instances
IArray (IOToDiffArray IOArray) e
(Typeable a, Typeable b) => Typeable (IOArray a b)
HasBounds IOArray
MArray IOArray e IO
Eq (IOArray i e)
newIOArray :: (Ix i) => (i, i) -> e -> IO (IOArray i e)
Build a new IOArray
unsafeReadIOArray :: (Ix i) => IOArray i e -> Int -> IO e
Read a value from an IOArray
unsafeWriteIOArray :: (Ix i) => IOArray i e -> Int -> e -> IO ()
Write a new value into an IOArray
readIOArray :: (Ix i) => IOArray i e -> i -> IO e
Read a value from an IOArray
writeIOArray :: (Ix i) => IOArray i e -> i -> e -> IO ()
Write a new value into an IOArray
data Exception
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).
Constructors
ArithException ArithExceptionExceptions raised by arithmetic operations. (NOTE: GHC currently does not throw ArithExceptions except for DivideByZero).
ArrayException ArrayExceptionExceptions raised by array-related operations. (NOTE: GHC currently does not throw ArrayExceptions).
AssertionFailed StringThis 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 AsyncExceptionAsynchronous exceptions (see section on Asynchronous Exceptions: Control.Exception#AsynchronousExceptions).
BlockedOnDeadMVarThe current thread was executing a call to takeMVar that could never return, because there are no other references to this MVar.
DeadlockThere are no runnable threads, so the program is deadlocked. The Deadlock exception is raised in the main thread only (see also: Control.Concurrent).
DynException DynamicDynamically typed exceptions (see section on Dynamic Exceptions: Control.Exception#DynamicExceptions).
ErrorCall StringThe ErrorCall exception is thrown by error. The String argument of ErrorCall is the string passed to error when it was called.
ExitException ExitCodeThe ExitException exception is thrown by exitWith (and exitFailure). The ExitCode argument is the value passed to exitWith. An unhandled ExitException exception in the main thread will cause the program to be terminated with the given exit code.
IOException IOExceptionThese are the standard IO exceptions generated by Haskell's IO operations. See also System.IO.Error.
NoMethodError StringAn 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.
NonTerminationThe current thread is stuck in an infinite loop. This exception may or may not be thrown when the program is non-terminating.
PatternMatchFail StringA pattern matching failure. The String argument should contain a descriptive message including the function name, source file and line number.
RecConError StringAn 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 StringA 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 StringAn 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.
Instances
Typeable Exception
Show Exception
Eq Exception
data ArithException
The type of arithmetic exceptions
Constructors
Overflow
Underflow
LossOfPrecision
DivideByZero
Denormal
Instances
Typeable ArithException
Show ArithException
Eq ArithException
Ord ArithException
data AsyncException
Asynchronous exceptions
Constructors
StackOverflowThe 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.
ThreadKilledThis exception is raised by another thread calling killThread, or by the system if it needs to terminate the thread for some reason.
Instances
Typeable AsyncException
Show AsyncException
Eq AsyncException
Ord AsyncException
data ArrayException
Exceptions generated by array operations
Constructors
IndexOutOfBounds StringAn attempt was made to index an array outside its declared bounds.
UndefinedElement StringAn attempt was made to evaluate an element of an array that had not been initialized.
Instances
Typeable ArrayException
Show ArrayException
Eq ArrayException
Ord ArrayException
stackOverflow :: Exception
heapOverflow :: Exception
data ExitCode
Constructors
ExitSuccess
ExitFailure Int
Instances
Eq ExitCode
Ord ExitCode
Read ExitCode
Show ExitCode
throw :: Exception -> a
Throw an exception. Exceptions may be thrown from purely functional code, but may only be caught within the IO monad.
throwIO :: Exception -> IO a

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.

ioException :: IOException -> IO a
ioError :: IOError -> IO a
type IOError = IOException
The Haskell 98 type for exceptions in the IO monad. In Haskell 98, this is an opaque type.
data 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.
Constructors
IOError
ioe_handle :: (Maybe Handle)
ioe_type :: IOErrorType
ioe_location :: String
ioe_description :: String
ioe_filename :: (Maybe FilePath)
Instances
Typeable IOException
Eq IOException
Show IOException
data IOErrorType
Constructors
AlreadyExists
NoSuchThing
ResourceBusy
ResourceExhausted
EOF
IllegalOperation
PermissionDenied
UserError
UnsatisfiedConstraints
SystemError
ProtocolError
OtherError
InvalidArgument
InappropriateType
HardwareFault
UnsupportedOperation
TimeExpired
ResourceVanished
Interrupted
DynIOError Dynamic
Instances
Eq IOErrorType
Show IOErrorType
userError :: String -> IOError
data IOMode
Constructors
ReadMode
WriteMode
AppendMode
ReadWriteMode
Instances
Eq IOMode
Ord IOMode
Ix IOMode
Enum IOMode
Read IOMode
Show IOMode
Produced by Haddock version 0.4