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) |
Safe Haskell | Unsafe |
Language | Haskell2010 |
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 #)
- liftIO :: IO a -> State# RealWorld -> STret RealWorld a
- mplusIO :: IO a -> IO a -> IO a
- unsafePerformIO :: IO a -> a
- unsafeInterleaveIO :: IO a -> IO a
- unsafeDupablePerformIO :: IO a -> a
- unsafeDupableInterleaveIO :: IO a -> IO a
- noDuplicate :: IO ()
- stToIO :: ST RealWorld a -> IO a
- ioToST :: IO a -> ST RealWorld a
- unsafeIOToST :: IO a -> ST s a
- unsafeSTToIO :: ST s a -> IO a
- type FilePath = String
- catch :: Exception e => IO a -> (e -> IO a) -> IO a
- catchException :: Exception e => IO a -> (e -> IO a) -> IO a
- catchAny :: IO a -> (forall e. Exception e => e -> IO a) -> IO a
- throwIO :: Exception e => e -> IO a
- mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b
- mask_ :: IO a -> IO a
- uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b
- uninterruptibleMask_ :: IO a -> IO a
- data MaskingState
- getMaskingState :: IO MaskingState
- unsafeUnmask :: IO a -> IO a
- interruptible :: IO a -> IO a
- onException :: IO a -> IO b -> IO a
- bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c
- finally :: IO a -> IO b -> IO a
- evaluate :: a -> IO a
- mkUserError :: [Char] -> SomeException
Documentation
A value of type
is a computation which, when performed,
does some I/O before returning a value of type IO
aa
.
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.
Instances
MonadFail IO Source # | Since: base-4.9.0.0 |
MonadFix IO Source # | Since: base-2.1 |
MonadIO IO Source # | Since: base-4.9.0.0 |
Alternative IO Source # | Takes the first non-throwing Since: base-4.9.0.0 |
Applicative IO Source # | Since: base-2.1 |
Functor IO Source # | Since: base-2.1 |
Monad IO Source # | Since: base-2.1 |
MonadPlus IO Source # | Takes the first non-throwing Since: base-4.9.0.0 |
GHCiSandboxIO IO Source # | Since: base-4.4.0.0 |
Monoid a => Monoid (IO a) Source # | Since: base-4.9.0.0 |
Semigroup a => Semigroup (IO a) Source # | Since: base-4.10.0.0 |
a ~ () => HPrintfType (IO a) Source # | Since: base-4.7.0.0 |
Defined in Text.Printf | |
a ~ () => PrintfType (IO a) Source # | Since: base-4.7.0.0 |
Defined in Text.Printf |
unsafePerformIO :: IO a -> a Source #
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. Furthermore, when using
unsafePerformIO
to cause side-effects, you should take the following
precautions to ensure the side effects are performed as many times as
you expect them to be. Note that these precautions are necessary for
GHC, but may not be sufficient, and other compilers may require
different precautions:
- Use
{-# NOINLINE foo #-}
as a pragma on any functionfoo
that callsunsafePerformIO
. 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 (liketest
in the example below). - Make sure that the either you switch off let-floating (
-fno-full-laziness
), or that the call tounsafePerformIO
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 tof
. Better would bef 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!
WARNING: If you're looking for "a way to get a String
from an 'IO String'",
then unsafePerformIO
is not the way to go. Learn about do-notation and the
<-
syntax element before you proceed.
unsafeInterleaveIO :: IO a -> IO a Source #
unsafeInterleaveIO
allows an 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
.
unsafeDupablePerformIO :: IO a -> a Source #
This version of unsafePerformIO
is more efficient
because it omits the check that the IO is only being performed by a
single thread. Hence, when you use unsafeDupablePerformIO
,
there is a possibility that the IO action may be performed multiple
times (on a multiprocessor), and you should therefore ensure that
it gives the same results each time. It may even happen that one
of the duplicated IO actions is only run partially, and then interrupted
in the middle without an exception being raised. Therefore, functions
like bracket
cannot be used safely within
unsafeDupablePerformIO
.
Since: base-4.4.0.0
unsafeDupableInterleaveIO :: IO a -> IO a Source #
unsafeDupableInterleaveIO
allows an 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.
The computation may be performed multiple times by different threads,
possibly at the same time. To ensure that the computation is performed
only once, use unsafeInterleaveIO
instead.
noDuplicate :: IO () Source #
Ensures that the suspensions under evaluation by the current thread
are unique; that is, the current thread is not evaluating anything
that is also under evaluation by another thread that has also executed
noDuplicate
.
This operation is used in the definition of unsafePerformIO
to
prevent the IO action from being executed multiple times, which is usually
undesirable.
unsafeIOToST :: IO a -> ST s a Source #
unsafeSTToIO :: ST s a -> IO a Source #
Convert an ST
action to an IO
action.
This relies on IO
and ST
having the same representation modulo the
constraint on the state thread type parameter.
For an example demonstrating why this is unsafe, see https://mail.haskell.org/pipermail/haskell-cafe/2009-April/060719.html
type FilePath = String Source #
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.
:: Exception e | |
=> IO a | The computation to run |
-> (e -> IO a) | Handler to invoke if an exception is raised |
-> IO a |
This is the simplest of the exception-catching functions. It takes a single argument, runs it, and if an exception is raised the "handler" is executed, with the value of the exception passed as an argument. Otherwise, the result is returned as normal. For example:
catch (readFile f) (\e -> do let err = show (e :: IOException) hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ err) return "")
Note that we have to give a type signature to e
, or the program
will not typecheck as the type is ambiguous. While it is possible
to catch exceptions of any type, see the section "Catching all
exceptions" (in Control.Exception) for an explanation of the problems with doing so.
For catching exceptions in pure (non-IO
) expressions, see the
function evaluate
.
Note that due to Haskell's unspecified evaluation order, an
expression may throw one of several possible exceptions: consider
the expression (error "urk") + (1 `div` 0)
. Does
the expression throw
ErrorCall "urk"
, or DivideByZero
?
The answer is "it might throw either"; the choice is
non-deterministic. If you are catching any type of exception then you
might catch either. If you are calling catch
with type
IO Int -> (ArithException -> IO Int) -> IO Int
then the handler may
get run with DivideByZero
as an argument, or an ErrorCall "urk"
exception may be propagated further up. If you call it again, you
might get the opposite behaviour. This is ok, because catch
is an
IO
computation.
catchException :: Exception e => IO a -> (e -> IO a) -> IO a Source #
Catch an exception in the IO
monad.
Note that this function is strict in the action. That is,
catchException undefined b == _|_
. See
for details.
throwIO :: Exception e => e -> IO a Source #
A variant of throw
that can only 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` () ===> throw e throwIO e `seq` () ===> ()
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 operations, whereas throw
does not. We say that throwIO
throws *precise* exceptions and
throw
, error
, etc. all throw *imprecise* exceptions.
For example
throw e + error "boom" ===> error "boom" throw e + error "boom" ===> throw e
are both valid reductions and the compiler may pick any (loop, even), whereas
throwIO e >> error "boom" ===> throwIO e
will always throw e
when executed.
See also the GHC wiki page on precise exceptions for a more technical introduction to how GHC optimises around precise vs. imprecise exceptions.
mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b Source #
Executes an IO computation with asynchronous
exceptions masked. That is, any thread which attempts to raise
an exception in the current thread with throwTo
will be blocked until asynchronous exceptions are unmasked again.
The argument passed to mask
is a function that takes as its
argument another function, which can be used to restore the
prevailing masking state within the context of the masked
computation. For example, a common way to use mask
is to protect
the acquisition of a resource:
mask $ \restore -> do x <- acquire restore (do_something_with x) `onException` release release
This code guarantees that acquire
is paired with release
, by masking
asynchronous exceptions for the critical parts. (Rather than write
this code yourself, it would be better to use
bracket
which abstracts the general pattern).
Note that the restore
action passed to the argument to mask
does not necessarily unmask asynchronous exceptions, it just
restores the masking state to that of the enclosing context. Thus
if asynchronous exceptions are already masked, mask
cannot be used
to unmask exceptions again. This is so that if you call a library function
with exceptions masked, you can be sure that the library call will not be
able to unmask exceptions again. If you are writing library code and need
to use asynchronous exceptions, the only way is to create a new thread;
see forkIOWithUnmask
.
Asynchronous exceptions may still be received while in the masked state if the masked thread blocks in certain ways; see Control.Exception.
Threads created by forkIO
inherit the
MaskingState
from the parent; that is, to start a thread in the
MaskedInterruptible
state,
use mask_ $ forkIO ...
. This is particularly useful if you need
to establish an exception handler in the forked thread before any
asynchronous exceptions are received. To create a new thread in
an unmasked state use forkIOWithUnmask
.
uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b Source #
Like mask
, but the masked computation is not interruptible (see
Control.Exception). THIS SHOULD BE USED WITH
GREAT CARE, because if a thread executing in uninterruptibleMask
blocks for any reason, then the thread (and possibly the program,
if this is the main thread) will be unresponsive and unkillable.
This function should only be necessary if you need to mask
exceptions around an interruptible operation, and you can guarantee
that the interruptible operation will only block for a short period
of time.
uninterruptibleMask_ :: IO a -> IO a Source #
Like uninterruptibleMask
, but does not pass a restore
action
to the argument.
data MaskingState Source #
Describes the behaviour of a thread when an asynchronous exception is received.
Unmasked | asynchronous exceptions are unmasked (the normal state) |
MaskedInterruptible | the state during |
MaskedUninterruptible | the state during |
Instances
Show MaskingState Source # | Since: base-4.3.0.0 |
Eq MaskingState Source # | Since: base-4.3.0.0 |
Defined in GHC.IO (==) :: MaskingState -> MaskingState -> Bool Source # (/=) :: MaskingState -> MaskingState -> Bool Source # |
getMaskingState :: IO MaskingState Source #
Returns the MaskingState
for the current thread.
unsafeUnmask :: IO a -> IO a Source #
interruptible :: IO a -> IO a Source #
Allow asynchronous exceptions to be raised even inside mask
, making
the operation interruptible (see the discussion of "Interruptible operations"
in Exception
).
When called outside mask
, or inside uninterruptibleMask
, this
function has no effect.
Since: base-4.9.0.0
evaluate :: a -> IO a Source #
Evaluate the argument to weak head normal form.
evaluate
is typically used to uncover any exceptions that a lazy value
may contain, and possibly handle them.
evaluate
only evaluates to weak head normal form. If deeper
evaluation is needed, the force
function from Control.DeepSeq
may be handy:
evaluate $ force x
There is a subtle difference between
and evaluate
x
,
analogous to the difference between return
$!
xthrowIO
and throw
. If the lazy
value x
throws an exception,
will fail to return an
return
$!
xIO
action and will throw an exception instead.
, on the
other hand, always produces an evaluate
xIO
action; that action will throw an
exception upon execution iff x
throws an exception upon evaluation.
The practical implication of this difference is that due to the imprecise exceptions semantics,
(return $! error "foo") >> error "bar"
may throw either "foo"
or "bar"
, depending on the optimizations
performed by the compiler. On the other hand,
evaluate (error "foo") >> error "bar"
is guaranteed to throw "foo"
.
The rule of thumb is to use evaluate
to force or handle exceptions in
lazy values. If, on the other hand, you are forcing a lazy value for
efficiency reasons only and do not care about exceptions, you may
use
.return
$!
x
mkUserError :: [Char] -> SomeException Source #