liblawless-0.25.2: Prelude based on protolude for GHC 8 and beyond.

Copyright© 2016 All rights reserved.
LicenseGPL-3
MaintainerEvan Cofsky <evan@theunixman.com>
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

IO

Description

 

Synopsis

Documentation

getLine :: (MonadIO m, MonadThrow m, Textual t) => m t Source #

Read and parse a 'Textual" from stdin.

hGetLine :: (MonadIO m, MonadThrow m, Textual t) => Handle -> m t Source #

Read and parse a Textual from a Handle.

putStr :: MonadIO m => Builder -> m () Source #

Write a Printer to stdout.

putStrLn :: MonadIO m => Builder -> m () Source #

Write a Printer plus a newline to stdout.

hPutStr :: MonadIO m => Handle -> Builder -> m () Source #

Write a Printer to a Handle.

hPutStrLn :: MonadIO m => Handle -> Builder -> m () Source #

Write a Printer plus a newline to stderr.

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.

Minimal complete definition

throwM

Instances

MonadThrow [] 

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 

Methods

throwM :: Exception e => e -> Maybe a #

MonadThrow IO 

Methods

throwM :: Exception e => e -> IO a #

MonadThrow Q 

Methods

throwM :: Exception e => e -> Q a #

MonadThrow STM 

Methods

throwM :: Exception e => e -> STM a #

(~) * e SomeException => MonadThrow (Either e) 

Methods

throwM :: Exception e => e -> Either e a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> MaybeT m a #

Monad m => MonadThrow (CatchT m) 

Methods

throwM :: Exception e => e -> CatchT m a #

MonadThrow m => MonadThrow (IterT m) 

Methods

throwM :: Exception e => e -> IterT m a #

MonadThrow m => MonadThrow (ListT m) 

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (ResourceT m) 

Methods

throwM :: Exception e => e -> ResourceT m a #

MonadThrow m => MonadThrow (IdentityT * m) 

Methods

throwM :: Exception e => e -> IdentityT * m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 

Methods

throwM :: Exception e => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (StateT s m) 

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 

Methods

throwM :: Exception e => e -> StateT s m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> ErrorT e m a #

(Functor f, MonadThrow m) => MonadThrow (FreeT f m) 

Methods

throwM :: Exception e => e -> FreeT f m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> ExceptT e m a #

MonadThrow m => MonadThrow (ReaderT * r m) 

Methods

throwM :: Exception e => e -> ReaderT * r m a #

MonadThrow m => MonadThrow (ConduitM i o m) 

Methods

throwM :: Exception e => e -> ConduitM i o m a #

MonadThrow m => MonadThrow (ContT * r m) 

Methods

throwM :: Exception e => e -> ContT * r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

Methods

throwM :: Exception e => e -> RWST r w s m a #

MonadThrow m => MonadThrow (Pipe l i o u m) 

Methods

throwM :: Exception e => e -> Pipe l i o u m a #

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.

Minimal complete definition

catch

Instances

MonadCatch IO 

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a #

MonadCatch STM 

Methods

catch :: Exception e => STM a -> (e -> STM a) -> STM a #

(~) * e SomeException => MonadCatch (Either e)

Since: 0.8.3

Methods

catch :: Exception e => Either e a -> (e -> Either e a) -> Either e a #

MonadCatch m => MonadCatch (MaybeT m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a #

Monad m => MonadCatch (CatchT m) 

Methods

catch :: Exception e => CatchT m a -> (e -> CatchT m a) -> CatchT m a #

MonadCatch m => MonadCatch (IterT m) 

Methods

catch :: Exception e => IterT m a -> (e -> IterT m a) -> IterT m a #

MonadCatch m => MonadCatch (ListT m) 

Methods

catch :: Exception e => ListT m a -> (e -> ListT m a) -> ListT m a #

MonadCatch m => MonadCatch (ResourceT m) 

Methods

catch :: Exception e => ResourceT m a -> (e -> ResourceT m a) -> ResourceT m a #

MonadCatch m => MonadCatch (IdentityT * m) 

Methods

catch :: Exception e => IdentityT * m a -> (e -> IdentityT * m a) -> IdentityT * m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

MonadCatch m => MonadCatch (StateT s m) 

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadCatch m => MonadCatch (StateT s m) 

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

(Error e, MonadCatch m) => MonadCatch (ErrorT e m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a #

(Functor f, MonadCatch m) => MonadCatch (FreeT f m) 

Methods

catch :: Exception e => FreeT f m a -> (e -> FreeT f m a) -> FreeT f m a #

MonadCatch m => MonadCatch (ExceptT e m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a #

MonadCatch m => MonadCatch (ReaderT * r m) 

Methods

catch :: Exception e => ReaderT * r m a -> (e -> ReaderT * r m a) -> ReaderT * r m a #

MonadCatch m => MonadCatch (ConduitM i o m) 

Methods

catch :: Exception e => ConduitM i o m a -> (e -> ConduitM i o m a) -> ConduitM i o m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

MonadCatch m => MonadCatch (Pipe l i o u m) 

Methods

catch :: Exception e => Pipe l i o u m a -> (e -> Pipe l i o u m a) -> Pipe l i o u m a #

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.

Minimal complete definition

mask, uninterruptibleMask

Instances

MonadMask IO 

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

(~) * e SomeException => MonadMask (Either e)

Since: 0.8.3

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

Monad m => MonadMask (CatchT m)

Note: This instance is only valid if the underlying monad has a single exit point!

Methods

mask :: ((forall a. CatchT m a -> CatchT m a) -> CatchT m b) -> CatchT m b #

uninterruptibleMask :: ((forall a. CatchT m a -> CatchT m a) -> CatchT m b) -> CatchT m b #

MonadMask m => MonadMask (ResourceT m) 

Methods

mask :: ((forall a. ResourceT m a -> ResourceT m a) -> ResourceT m b) -> ResourceT m b #

uninterruptibleMask :: ((forall a. ResourceT m a -> ResourceT m a) -> ResourceT m b) -> ResourceT m b #

MonadMask m => MonadMask (IdentityT * m) 

Methods

mask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

uninterruptibleMask :: ((forall a. IdentityT * m a -> IdentityT * m a) -> IdentityT * m b) -> IdentityT * m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

MonadMask m => MonadMask (StateT s m) 

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

MonadMask m => MonadMask (ReaderT * r m) 

Methods

mask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

uninterruptibleMask :: ((forall a. ReaderT * r m a -> ReaderT * r m a) -> ReaderT * r m b) -> ReaderT * r m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

data Handle :: * #

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.

Instances

Eq Handle 

Methods

(==) :: Handle -> Handle -> Bool #

(/=) :: Handle -> Handle -> Bool #

Show Handle 

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.

withCurrentPosition :: (MonadIO m, MonadMask m) => Handle -> (Handle -> m a) -> m a Source #

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:

Minimal complete definition

liftIO

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (CatchT m) 

Methods

liftIO :: IO a -> CatchT m a #

MonadIO m => MonadIO (IterT m) 

Methods

liftIO :: IO a -> IterT m a #

MonadIO m => MonadIO (ListT m) 

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (ResourceT m) 

Methods

liftIO :: IO a -> ResourceT m a #

MonadIO m => MonadIO (IdentityT * m) 

Methods

liftIO :: IO a -> IdentityT * m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

(Functor f, MonadIO m) => MonadIO (FreeT f m) 

Methods

liftIO :: IO a -> FreeT f m a #

MonadIO m => MonadIO (ExceptT e m) 

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (PlanT k o m) 

Methods

liftIO :: IO a -> PlanT k o m a #

MonadIO m => MonadIO (ReaderT * r m) 

Methods

liftIO :: IO a -> ReaderT * r m a #

MonadIO m => MonadIO (ConduitM i o m) 

Methods

liftIO :: IO a -> ConduitM i o m a #

MonadIO m => MonadIO (ContT * r m) 

Methods

liftIO :: IO a -> ContT * r m a #

MonadIO m => MonadIO (ParsecT s u m) 

Methods

liftIO :: IO a -> ParsecT s u m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

MonadIO m => MonadIO (Pipe l i o u m) 

Methods

liftIO :: IO a -> Pipe l i o u m a #

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

binaryFile :: (MonadIO m, MonadMask m, AbsRel ar) => File ar -> IOMode -> (Handle -> m a) -> m a Source #

Binary files, no buffering.

textFile :: (MonadIO m, MonadMask m, AbsRel ar) => File ar -> IOMode -> (Handle -> m a) -> m a Source #

Text files, line-buffered.

close :: MonadIO m => Handle -> m () Source #

doesFileExist :: (MonadIO m, AbsRel ar) => File ar -> m Bool Source #

removeFile :: (MonadIO m, AbsRel ar) => File ar -> m () Source #

stdin :: Handle #

A handle managing input from the Haskell program's standard input channel.

stdout :: Handle #

A handle managing output to the Haskell program's standard output channel.

stderr :: Handle #

A handle managing output to the Haskell program's standard error channel.