Safe Haskell | None |
---|---|
Language | Haskell2010 |
Re-exports of Haskell base and GHC system libraries.
Synopsis
- liftIO :: MonadIO m => IO a -> m a
- class Monad m => MonadIO (m :: Type -> Type)
- data Handle
- data IOMode
- withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
- stdin :: Handle
- stdout :: Handle
- stderr :: Handle
- hFlush :: Handle -> IO ()
- unsafePerformIO :: IO a -> a
- class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- data SomeException
- throw :: (MonadThrow m, Exception e) => e -> m a
- impureThrow :: Exception e => e -> a
- bracket :: MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c
- catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a
- finally :: MonadMask m => m a -> m b -> m a
Input/Output
from Control.Monad.IO.Class
Re-exported from Control.Monad.IO.Class in base:
class Monad m => MonadIO (m :: Type -> Type) #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
MonadIO IO | Since: base-4.9.0.0 |
Defined in Control.Monad.IO.Class | |
MonadIO Q | |
Defined in Language.Haskell.TH.Syntax | |
MonadIO Sh | |
Defined in Shelly.Base | |
MonadIO (Program τ) Source # | |
Defined in Core.Program.Context | |
MonadIO m => MonadIO (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) | |
Defined in Control.Monad.Trans.Error |
from System.IO
Re-exported from System.IO in base:
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.
See openFile
withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r #
opens a file using withFile
name mode actopenFile
and passes
the resulting handle to the computation act
. The handle will be
closed on exit from withFile
, whether by normal termination or by
raising an exception. If closing the handle raises an exception, then
this exception will be raised by withFile
rather than any exception
raised by act
.
The action hFlush
hdl
causes any items buffered for output
in handle hdl
to be sent immediately to the operating system.
This operation may fail with:
isFullError
if the device is full;isPermissionError
if a system resource limit would be exceeded. It is unspecified whether the characters in the buffer are discarded or retained under these circumstances.
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. 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!
Exception handling
from Control.Exception.Safe
Re-exported from Control.Exception.Safe in the safe-exceptions package:
class (Typeable e, Show e) => Exception e where #
Any type that you wish to throw or catch as an exception must be an
instance of the Exception
class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException deriving Show instance Exception MyException
The default method definitions in the Exception
class do what we need
in this case. You can now throw and catch ThisException
and
ThatException
as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
--------------------------------------------------------------------- -- Make the root exception type for all the exceptions in a compiler data SomeCompilerException = forall e . Exception e => SomeCompilerException e instance Show SomeCompilerException where show (SomeCompilerException e) = show e instance Exception SomeCompilerException compilerExceptionToException :: Exception e => e -> SomeException compilerExceptionToException = toException . SomeCompilerException compilerExceptionFromException :: Exception e => SomeException -> Maybe e compilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a --------------------------------------------------------------------- -- Make a subhierarchy for exceptions in the frontend of the compiler data SomeFrontendException = forall e . Exception e => SomeFrontendException e instance Show SomeFrontendException where show (SomeFrontendException e) = show e instance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromException frontendExceptionToException :: Exception e => e -> SomeException frontendExceptionToException = toException . SomeFrontendException frontendExceptionFromException :: Exception e => SomeException -> Maybe e frontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a --------------------------------------------------------------------- -- Make an exception type for a particular frontend compiler exception data MismatchedParentheses = MismatchedParentheses deriving Show instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Nothing
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
Render this exception value in a human-friendly manner.
Default implementation:
.show
Since: base-4.8.0.0
Instances
data SomeException #
The SomeException
type is the root of the exception type hierarchy.
When an exception of type e
is thrown, behind the scenes it is
encapsulated in a SomeException
.
Instances
Show SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS # | |
Exception SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type |
throw :: (MonadThrow m, Exception e) => e -> m a #
Synchronously throw the given exception
Since: safe-exceptions-0.1.0.0
impureThrow :: Exception e => e -> a #
Generate a pure value which, when forced, will synchronously throw the given exception
Generally it's better to avoid using this function and instead use throw
,
see https://github.com/fpco/safe-exceptions#quickstart
Since: safe-exceptions-0.1.0.0
bracket :: MonadMask m => m a -> (a -> m b) -> (a -> m c) -> m c #
Async safe version of bracket
Since: safe-exceptions-0.1.0.0
catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a #
Same as upstream catch
, but will not catch asynchronous
exceptions
Since: safe-exceptions-0.1.0.0