Copyright | © 2016 All rights reserved. |
---|---|
License | GPL-3 |
Maintainer | Evan Cofsky <evan@theunixman.com> |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
- data IO a :: * -> *
- getLine :: (MonadIO m, MonadThrow m, Textual t) => m t
- hGetLine :: (MonadIO m, MonadThrow m, Textual t) => Handle -> m t
- putStr :: MonadIO m => Builder -> m ()
- putStrLn :: MonadIO m => Builder -> m ()
- hPutStr :: MonadIO m => Handle -> Builder -> m ()
- hPutStrLn :: MonadIO m => Handle -> Builder -> m ()
- data ParseError
- peReason :: Lens' ParseError Text
- peStack :: Lens' ParseError [Text]
- class Monad m => MonadThrow (m :: * -> *)
- class MonadThrow m => MonadCatch (m :: * -> *)
- class MonadCatch m => MonadMask (m :: * -> *)
- data Handle :: *
- data TemporaryFile
- tfPath :: Lens' TemporaryFile AbsFile
- tfHandle :: Lens' TemporaryFile Handle
- binaryTemporaryFile :: (MonadIO m, MonadMask m, MonadThrow m) => AbsDir -> RelFile -> (TemporaryFile -> m a) -> m a
- textTemporaryFile :: (MonadIO m, MonadMask m, MonadThrow m) => AbsDir -> RelFile -> (TemporaryFile -> m a) -> m a
- withOffset :: (MonadIO m, MonadMask m) => Handle -> FileOffset -> (Handle -> m a) -> m a
- withPosition :: (MonadIO m, MonadMask m) => Handle -> FilePosition -> (Handle -> m a) -> m a
- withCurrentPosition :: (MonadIO m, MonadMask m) => Handle -> (Handle -> m a) -> m a
- class Monad m => MonadIO (m :: * -> *) where
- liftIO :: MonadIO m => forall a. IO a -> m a
- data IOMode :: *
- binaryFile :: (MonadIO m, MonadMask m, AbsRel ar) => File ar -> IOMode -> (Handle -> m a) -> m a
- textFile :: (MonadIO m, MonadMask m, AbsRel ar) => File ar -> IOMode -> (Handle -> m a) -> m a
- isEOF :: MonadIO m => Handle -> m Bool
- close :: MonadIO m => Handle -> m ()
- doesFileExist :: (MonadIO m, AbsRel ar) => File ar -> m Bool
- removeFile :: (MonadIO m, AbsRel ar) => File ar -> m ()
- stdin :: Handle
- stdout :: Handle
- stderr :: Handle
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.
Monad IO | Since: 2.1 |
Functor IO | Since: 2.1 |
MonadFix IO | Since: 2.1 |
MonadFail IO | Since: 4.9.0.0 |
Applicative IO | Since: 2.1 |
Alternative IO | Since: 4.9.0.0 |
MonadPlus IO | Since: 4.9.0.0 |
MonadIO IO | Since: 4.9.0.0 |
MonadThrow IO | |
MonadCatch IO | |
MonadMask IO | |
PrimMonad IO | |
PrimBase IO | |
Quasi IO | |
MonadBaseControl IO IO | |
MonadBase IO IO | |
Semigroup a => Semigroup (IO a) | Since: 4.10.0.0 |
Monoid a => Monoid (IO a) | Since: 4.9.0.0 |
type PrimState IO | |
type StM IO a | |
getLine :: (MonadIO m, MonadThrow m, Textual t) => m t Source #
Read and parse a 'Textual" from stdin
.
data ParseError Source #
Exception representing a failure to parse a Textual
.
class Monad m => MonadThrow (m :: * -> *) #
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
MonadThrow [] | |
MonadThrow Maybe | |
MonadThrow IO | |
MonadThrow Q | |
MonadThrow STM | |
(~) * e SomeException => MonadThrow (Either e) | |
MonadThrow m => MonadThrow (MaybeT m) | Throws exceptions into the base monad. |
MonadThrow m => MonadThrow (ListT m) | |
MonadThrow m => MonadThrow (ResourceT m) | |
MonadThrow m => MonadThrow (IdentityT * m) | |
(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) | |
(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) | |
MonadThrow m => MonadThrow (StateT s m) | |
MonadThrow m => MonadThrow (StateT s m) | |
(Error e, MonadThrow m) => MonadThrow (ErrorT e m) | Throws exceptions into the base monad. |
MonadThrow m => MonadThrow (ExceptT e m) | Throws exceptions into the base monad. |
MonadThrow m => MonadThrow (ReaderT * r m) | |
MonadThrow m => MonadThrow (ConduitM i o m) | |
MonadThrow m => MonadThrow (ContT * r m) | |
(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) | |
(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) | |
MonadThrow m => MonadThrow (Pipe l i o u m) | |
class MonadThrow m => MonadCatch (m :: * -> *) #
A class for monads which allow exceptions to be caught, in particular
exceptions which were thrown by throwM
.
Instances should obey the following law:
catch (throwM e) f = f e
Note that the ability to catch an exception does not guarantee that we can
deal with all possible exit points from a computation. Some monads, such as
continuation-based stacks, allow for more than just a success/failure
strategy, and therefore catch
cannot be used by those monads to properly
implement a function such as finally
. For more information, see
MonadMask
.
MonadCatch IO | |
MonadCatch STM | |
(~) * e SomeException => MonadCatch (Either e) | Since: 0.8.3 |
MonadCatch m => MonadCatch (MaybeT m) | Catches exceptions from the base monad. |
MonadCatch m => MonadCatch (ListT m) | |
MonadCatch m => MonadCatch (ResourceT m) | |
MonadCatch m => MonadCatch (IdentityT * m) | |
(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) | |
(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) | |
MonadCatch m => MonadCatch (StateT s m) | |
MonadCatch m => MonadCatch (StateT s m) | |
(Error e, MonadCatch m) => MonadCatch (ErrorT e m) | Catches exceptions from the base monad. |
MonadCatch m => MonadCatch (ExceptT e m) | Catches exceptions from the base monad. |
MonadCatch m => MonadCatch (ReaderT * r m) | |
MonadCatch m => MonadCatch (ConduitM i o m) | |
(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) | |
(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) | |
MonadCatch m => MonadCatch (Pipe l i o u m) | |
class MonadCatch m => MonadMask (m :: * -> *) #
A class for monads which provide for the ability to account for all
possible exit points from a computation, and to mask asynchronous
exceptions. Continuation-based monads, and stacks such as ErrorT e IO
which provide for multiple failure modes, are invalid instances of this
class.
Note that this package does provide a MonadMask
instance for CatchT
.
This instance is only valid if the base monad provides no ability to
provide multiple exit. For example, IO
or Either
would be invalid base
monads, but Reader
or State
would be acceptable.
Instances should ensure that, in the following code:
f `finally` g
The action g
is called regardless of what occurs within f
, including
async exceptions.
MonadMask IO | |
(~) * e SomeException => MonadMask (Either e) | Since: 0.8.3 |
MonadMask m => MonadMask (ResourceT m) | |
MonadMask m => MonadMask (IdentityT * m) | |
(MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
(MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
MonadMask m => MonadMask (StateT s m) | |
MonadMask m => MonadMask (StateT s m) | |
MonadMask m => MonadMask (ReaderT * r m) | |
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
(MonadMask m, Monoid w) => MonadMask (RWST r w s m) | |
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.
data TemporaryFile Source #
binaryTemporaryFile :: (MonadIO m, MonadMask m, MonadThrow m) => AbsDir -> RelFile -> (TemporaryFile -> m a) -> m a Source #
textTemporaryFile :: (MonadIO m, MonadMask m, MonadThrow m) => AbsDir -> RelFile -> (TemporaryFile -> m a) -> m a Source #
withOffset :: (MonadIO m, MonadMask m) => Handle -> FileOffset -> (Handle -> m a) -> m a Source #
Save the current file position, seek relative to it, perform a function, and then return to the original position.
withPosition :: (MonadIO m, MonadMask m) => Handle -> FilePosition -> (Handle -> m a) -> m a Source #
Save the current file position, seek to a new position, perform a function, then return to the original position.
class Monad m => MonadIO (m :: * -> *) where #
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:
MonadIO IO | Since: 4.9.0.0 |
MonadIO m => MonadIO (MaybeT m) | |
MonadIO m => MonadIO (ListT m) | |
MonadIO m => MonadIO (ResourceT m) | |
MonadIO m => MonadIO (IdentityT * m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
MonadIO m => MonadIO (StateT s m) | |
MonadIO m => MonadIO (StateT s m) | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) | |
MonadIO m => MonadIO (ExceptT e m) | |
MonadIO m => MonadIO (ReaderT * r m) | |
MonadIO m => MonadIO (ConduitM i o m) | |
MonadIO m => MonadIO (PlanT k o m) | |
MonadIO m => MonadIO (ContT * r m) | |
MonadIO m => MonadIO (ParsecT s u m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
MonadIO m => MonadIO (Pipe l i o u m) | |
See openFile
binaryFile :: (MonadIO m, MonadMask m, AbsRel ar) => File ar -> IOMode -> (Handle -> m a) -> m a Source #
Binary files, no buffering.