|
GHC.IOBase | Portability | non-portable (GHC Extensions) | Stability | internal | Maintainer | cvs-ghc@haskell.org |
|
|
|
|
|
Description |
Definitions for the IO monad and its friends.
|
|
Synopsis |
|
|
|
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 | |
|
|
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. However, 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 | | Instances | |
|
|
data Handle |
|
|
type FD = Int |
|
data Handle__ |
|
|
type RawBuffer = MutableByteArray# RealWorld |
|
data Buffer |
|
|
data BufferState |
|
|
data BufferList |
|
|
bufferIsWritable :: Buffer -> Bool |
|
bufferEmpty :: Buffer -> Bool |
|
bufferFull :: Buffer -> Bool |
|
data HandleType |
Constructors | ClosedHandle | | SemiClosedHandle | | ReadHandle | | WriteHandle | | AppendHandle | | ReadWriteHandle | |
| Instances | |
|
|
type FilePath = String |
|
data BufferMode |
Constructors | NoBuffering | | LineBuffering | | BlockBuffering (Maybe Int) | |
|
|
|
newtype IORef a |
A mutable variable in the IO monad | Constructors | IORef (STRef RealWorld a) | |
| Instances | |
|
|
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 |
|
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). For backwards compatibility with Haskell 98, IOError is a type synonym
for Exception. | Constructors | ArithException ArithException | Exceptions raised by arithmetic
operations. (NOTE: GHC currently does not throw
ArithExceptions). | ArrayException ArrayException | Exceptions raised by array-related
operations. (NOTE: GHC currently does not throw
ArrayExceptions). | 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). | 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). | 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 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 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. |
| Instances | |
|
|
data ArithException |
The type of arithmetic exceptions | Constructors | Overflow | | Underflow | | LossOfPrecision | | DivideByZero | | Denormal | |
| Instances | |
|
|
data AsyncException |
Asynchronous exceptions | Constructors | 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: | ThreadKilled | This exception is raised by another thread
calling killThread, or by the system
if it needs to terminate the thread for some
reason. |
| Instances | |
|
|
data ArrayException |
Exceptions generated by array operations | Constructors | 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. |
| Instances | |
|
|
stackOverflow :: Exception |
|
heapOverflow :: Exception |
|
data ExitCode |
Constructors | ExitSuccess | | ExitFailure Int | |
|
|
|
throw :: Exception -> a |
Throw an exception. Exceptions may be thrown from purely
functional code, but may only be caught within the IO monad. |
|
ioError :: Exception -> IO a |
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. |
|
ioException :: IOException -> IO a |
|
type IOError = Exception |
|
data 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 | |
|
|
userError :: String -> IOError |
|
Produced by Haddock version 0.4 |