Safe Haskell | None |
---|---|
Language | Haskell2010 |
Simple interface for shell scripting-like tasks.
Synopsis
- data Shell a
- data ExitReason
- shell :: Shell a -> IO (Either ExitReason a)
- shell_ :: Shell a -> IO a
- exitString :: ExitReason -> String
- (|>) :: Shell () -> Shell () -> Shell ()
- capture :: Shell () -> Shell String
- captureStdErr :: Shell () -> Shell String
- capture2 :: Shell () -> Shell (String, String)
- capture3 :: Shell () -> Shell (String, String, ExitReason)
- stream :: (String -> String) -> Shell ()
- lift :: (String -> Shell String) -> Shell ()
- try :: Shell a -> Shell (Either String a)
- orElse :: Shell a -> Shell a -> Shell a
- exit :: Shell a
- class Guard guard where
- guard :: Guard g => g -> Shell (Result g)
- when :: Guard g => g -> Shell () -> Shell ()
- unless :: Guard g => g -> Shell () -> Shell ()
- withEnv :: String -> String -> Shell a -> Shell a
- withoutEnv :: String -> Shell a -> Shell a
- lookupEnv :: String -> Shell (Maybe String)
- getEnv :: String -> Shell String
- cmdline :: [String]
- class Monad m => MonadIO (m :: Type -> Type) where
- data Env = Env {}
- run :: FilePath -> [String] -> Shell ()
- sudo :: FilePath -> [String] -> Shell ()
- unsafeLiftIO :: IO a -> Shell a
- absPath :: Env -> FilePath -> FilePath
- shellEnv :: IO Env
- getShellEnv :: Shell Env
- joinResult :: Shell (Either ExitReason a) -> Shell a
- runSh :: Env -> Shell a -> IO (Either ExitReason a)
- cpdir :: FilePath -> FilePath -> Shell ()
- pwd :: Shell FilePath
- ls :: FilePath -> Shell [FilePath]
- mkdir :: Bool -> FilePath -> Shell ()
- rmdir :: FilePath -> Shell ()
- inDirectory :: FilePath -> Shell a -> Shell a
- isDirectory :: FilePath -> Shell Bool
- withHomeDirectory :: (FilePath -> Shell a) -> Shell a
- inHomeDirectory :: Shell a -> Shell a
- withAppDirectory :: String -> (FilePath -> Shell a) -> Shell a
- inAppDirectory :: FilePath -> Shell a -> Shell a
- forEachFile :: FilePath -> (FilePath -> Shell a) -> Shell [a]
- forEachFile_ :: FilePath -> (FilePath -> Shell ()) -> Shell ()
- forEachDirectory :: FilePath -> (FilePath -> Shell a) -> Shell [a]
- forEachDirectory_ :: FilePath -> (FilePath -> Shell ()) -> Shell ()
- isFile :: FilePath -> Shell Bool
- rm :: FilePath -> Shell ()
- mv :: FilePath -> FilePath -> Shell ()
- cp :: FilePath -> FilePath -> Shell ()
- input :: FilePath -> Shell String
- output :: FilePath -> String -> Shell ()
- withFile :: FilePath -> IOMode -> (Handle -> Shell a) -> Shell a
- withBinaryFile :: FilePath -> IOMode -> (Handle -> Shell a) -> Shell a
- openFile :: FilePath -> IOMode -> Shell Handle
- openBinaryFile :: FilePath -> IOMode -> Shell Handle
- data FileMode
- withTempFile :: FileMode -> (FilePath -> Handle -> Shell a) -> Shell a
- withCustomTempFile :: FileMode -> FilePath -> (FilePath -> Handle -> Shell a) -> Shell a
- withTempDirectory :: (FilePath -> Shell a) -> Shell a
- withCustomTempDirectory :: FilePath -> (FilePath -> Shell a) -> Shell a
- inTempDirectory :: Shell a -> Shell a
- inCustomTempDirectory :: FilePath -> Shell a -> Shell a
- data Handle
- data IOMode
- data BufferMode
- hFlush :: Handle -> Shell ()
- hClose :: Handle -> Shell ()
- hReady :: Handle -> Shell Bool
- hGetBuffering :: Handle -> Shell BufferMode
- hSetBuffering :: Handle -> BufferMode -> Shell ()
- getStdIn :: Shell Handle
- getStdOut :: Shell Handle
- getStdErr :: Shell Handle
- hPutStr :: Handle -> String -> Shell ()
- hPutStrLn :: Handle -> String -> Shell ()
- echo :: String -> Shell ()
- echo_ :: String -> Shell ()
- ask :: Shell String
- stdin :: Shell String
- hGetLine :: Handle -> Shell String
- hGetContents :: Handle -> Shell String
- data Color
- color :: Color -> String -> String
- background :: Color -> String -> String
- highlight :: String -> String
- bold :: String -> String
- underline :: String -> String
- hGetBytes :: Handle -> Int -> Shell ByteString
- hPutBytes :: Handle -> ByteString -> Shell ()
- hGetByteLine :: Handle -> Shell ByteString
- hGetByteContents :: Handle -> Shell ByteString
- module System.FilePath
- join :: Monad m => m (m a) -> m a
- class Applicative m => Monad (m :: Type -> Type) where
- class Functor (f :: Type -> Type) where
- fmap :: (a -> b) -> f a -> f b
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
- replicateM_ :: Applicative m => Int -> m a -> m ()
- replicateM :: Applicative m => Int -> m a -> m [a]
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m ()
- zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- forever :: Applicative f => f a -> f b
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- void :: Functor f => f a -> f ()
- ap :: Monad m => m (a -> b) -> m a -> m b
- liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
- liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
- liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
Running Shell programs
A shell command: either an IO computation or a pipeline of at least one step.
data ExitReason Source #
Why did the computation terminate?
Instances
Eq ExitReason Source # | |
Defined in Control.Shell.Internal (==) :: ExitReason -> ExitReason -> Bool # (/=) :: ExitReason -> ExitReason -> Bool # | |
Show ExitReason Source # | |
Defined in Control.Shell.Internal showsPrec :: Int -> ExitReason -> ShowS # show :: ExitReason -> String # showList :: [ExitReason] -> ShowS # |
shell :: Shell a -> IO (Either ExitReason a) Source #
Run a shell computation. If part of the computation fails, the whole computation fails. The computation's environment is initially that of the whole process.
shell_ :: Shell a -> IO a Source #
Run a shell computation and return its result. If the computation calls
exit
, the return value will be undefined. If the computation fails,
an error will be thrown.
exitString :: ExitReason -> String Source #
Convert an ExitReason
into a String
. Successful termination yields
the empty string, while abnormal termination yields the termination
error message. If the program terminaged abnormally but without an error
message - i.e. the error message is empty string - the error message will
be shown as "abnormal termination"
.
Error handling and control flow
(|>) :: Shell () -> Shell () -> Shell () infixl 5 Source #
Connect the standard output of the first argument to the standard input of the second argument, and run the two computations in parallel.
capture :: Shell () -> Shell String Source #
Perform the given computation and return its standard output.
captureStdErr :: Shell () -> Shell String Source #
Perform the given computation and return its standard error.
capture2 :: Shell () -> Shell (String, String) Source #
Perform the given computation and return its standard output and error, in that order.
capture3 :: Shell () -> Shell (String, String, ExitReason) Source #
Perform the given computation and return its standard output and error, as well as its exit reason, in that order.
stream :: (String -> String) -> Shell () Source #
Lift a pure function to a computation over standard input/output.
Similar to interact
.
lift :: (String -> Shell String) -> Shell () Source #
Lift a shell computation to a function over stdin and stdout.
Similar to interact
.
try :: Shell a -> Shell (Either String a) Source #
Attempt to run a computation. If the inner computation fails, the outer computations returns its error message, otherwise its result is returned.
orElse :: Shell a -> Shell a -> Shell a Source #
Attempt to run the first command. If the first command fails, run the second. Forces serialization of the first command.
class Guard guard where Source #
assert :: String -> guard -> Shell (Result guard) Source #
Perform a Shell computation; if the computation succeeds but returns a false-ish value, the outer Shell computation fails with the given error message.
guard :: Guard g => g -> Shell (Result g) Source #
Perform a Shell computation; if the computation succeeds but returns
a false-ish value, the outer Shell computation fails.
Corresponds to guard
.
when :: Guard g => g -> Shell () -> Shell () Source #
Perform the given computation if the given guard passes, otherwise do
nothing. The guard raising an error counts as failure as far as this
function is concerned.
Corresponds to when
.
unless :: Guard g => g -> Shell () -> Shell () Source #
Perform the given computation if the given guard fails, otherwise do
nothing. The guard raising an error counts as failure as far as this
function is concerned.
Corresponds to unless
.
Environment handling
withEnv :: String -> String -> Shell a -> Shell a Source #
Run a computation with the given environment variable set.
withoutEnv :: String -> Shell a -> Shell a Source #
Run a computation with the given environment variable unset.
lookupEnv :: String -> Shell (Maybe String) Source #
Get the value of an environment variable. Returns Nothing if the variable doesn't exist.
getEnv :: String -> Shell String Source #
Get the value of an environment variable. Returns the empty string if the variable doesn't exist.
Running external commands
class Monad m => MonadIO (m :: Type -> Type) 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:
Instances
MonadIO IO | Since: base-4.9.0.0 |
Defined in Control.Monad.IO.Class | |
MonadIO Q | |
Defined in Language.Haskell.TH.Syntax | |
MonadIO Shell Source # | |
Defined in Control.Shell.Base | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) | |
Defined in Control.Monad.Trans.Error |
A shell environment: consists of the current standard input, output and error handles used by the computation, as well as the current working directory and set of environment variables.
run :: FilePath -> [String] -> Shell () Source #
Execute an external command. No globbing, escaping or other external shell magic is performed on either the command or arguments. The program's stdout will be written to stdout.
unsafeLiftIO :: IO a -> Shell a Source #
Lift an IO computation into a shell. The lifted computation is not thread-safe, and should thus absolutely not use environment variables, relative paths or standard input/output.
absPath :: Env -> FilePath -> FilePath Source #
Create an absolute path from the environment and a potentially relative path. Has no effect if the path is already absolute.
getShellEnv :: Shell Env Source #
Get the complete environment for the current computation.
joinResult :: Shell (Either ExitReason a) -> Shell a Source #
Propagate an explicit ExitResult
through the computation.
Working with directories
cpdir :: FilePath -> FilePath -> Shell () Source #
Recursively copy a directory. If the target is a directory that already exists, the source directory is copied into that directory using its current name.
mkdir :: Bool -> FilePath -> Shell () Source #
Create a directory. Optionally create any required missing directories as well.
rmdir :: FilePath -> Shell () Source #
Recursively remove a directory. Follows symlinks, so be careful.
inDirectory :: FilePath -> Shell a -> Shell a Source #
Execute a command in the given working directory, then restore the previous working directory.
withHomeDirectory :: (FilePath -> Shell a) -> Shell a Source #
Do something with the user's home directory.
inHomeDirectory :: Shell a -> Shell a Source #
Perform an action with the user's home directory as the working directory.
withAppDirectory :: String -> (FilePath -> Shell a) -> Shell a Source #
Do something with the given application's data directory.
inAppDirectory :: FilePath -> Shell a -> Shell a Source #
Do something with the given application's data directory as the working directory.
forEachFile :: FilePath -> (FilePath -> Shell a) -> Shell [a] Source #
Perform an action on each file in the given directory. This function will traverse any subdirectories of the given as well. File paths are given relative to the given directory; the current working directory is not affected.
forEachFile_ :: FilePath -> (FilePath -> Shell ()) -> Shell () Source #
Like forEachFile
but only performs a side effect.
forEachDirectory :: FilePath -> (FilePath -> Shell a) -> Shell [a] Source #
Recursively perform an action on each subdirectory of the given directory. The path passed to the callback is relative to the given directory. The action will *not* be performed on the given directory itself.
forEachDirectory_ :: FilePath -> (FilePath -> Shell ()) -> Shell () Source #
Like forEachDirectory
, but discards its result.
Working with files
mv :: FilePath -> FilePath -> Shell () Source #
Rename a file or directory. If the target is a directory, then the source will be moved into that directory.
cp :: FilePath -> FilePath -> Shell () Source #
Copy a file. Fails if the source is a directory. If the target is a directory, the source file is copied into that directory using its current name.
withFile :: FilePath -> IOMode -> (Handle -> Shell a) -> Shell a Source #
Perform a computation over a file.
withBinaryFile :: FilePath -> IOMode -> (Handle -> Shell a) -> Shell a Source #
Perform a computation over a binary file.
openBinaryFile :: FilePath -> IOMode -> Shell Handle Source #
Open a file in binary mode, returning a handle to it.
Working with temporary files and directories
Perform a file operation in binary or text mode?
withTempFile :: FileMode -> (FilePath -> Handle -> Shell a) -> Shell a Source #
Create a temp file in the standard system temp directory, do something with it, then remove it.
withCustomTempFile :: FileMode -> FilePath -> (FilePath -> Handle -> Shell a) -> Shell a Source #
Create a temp file in the standard system temp directory, do something with it, then remove it.
withTempDirectory :: (FilePath -> Shell a) -> Shell a Source #
Create a temp directory in the standard system temp directory, do something with it, then remove it.
withCustomTempDirectory :: FilePath -> (FilePath -> Shell a) -> Shell a Source #
Create a temp directory in given directory, do something with it, then remove it.
inTempDirectory :: Shell a -> Shell a Source #
Performs a command inside a temporary directory. The directory will be cleaned up after the command finishes.
inCustomTempDirectory :: FilePath -> Shell a -> Shell a Source #
Performs a command inside a temporary directory. The directory will be cleaned up after the command finishes.
Working with handles
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
data BufferMode #
Three kinds of buffering are supported: line-buffering, block-buffering or no-buffering. These modes have the following effects. For output, items are written out, or flushed, from the internal buffer according to the buffer mode:
- line-buffering: the entire output buffer is flushed
whenever a newline is output, the buffer overflows,
a
hFlush
is issued, or the handle is closed. - block-buffering: the entire buffer is written out whenever it
overflows, a
hFlush
is issued, or the handle is closed. - no-buffering: output is written immediately, and never stored in the buffer.
An implementation is free to flush the buffer more frequently, but not less frequently, than specified above. The output buffer is emptied as soon as it has been written out.
Similarly, input occurs according to the buffer mode for the handle:
- line-buffering: when the buffer for the handle is not empty, the next item is obtained from the buffer; otherwise, when the buffer is empty, characters up to and including the next newline character are read into the buffer. No characters are available until the newline character is available or the buffer is full.
- block-buffering: when the buffer for the handle becomes empty, the next block of data is read into the buffer.
- no-buffering: the next input item is read and returned.
The
hLookAhead
operation implies that even a no-buffered handle may require a one-character buffer.
The default buffering mode when a handle is opened is implementation-dependent and may depend on the file system object which is attached to that handle. For most implementations, physical files will normally be block-buffered and terminals will normally be line-buffered.
NoBuffering | buffering is disabled if possible. |
LineBuffering | line-buffering should be enabled if possible. |
BlockBuffering (Maybe Int) | block-buffering should be enabled if possible.
The size of the buffer is |
Instances
Eq BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types (==) :: BufferMode -> BufferMode -> Bool # (/=) :: BufferMode -> BufferMode -> Bool # | |
Ord BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types compare :: BufferMode -> BufferMode -> Ordering # (<) :: BufferMode -> BufferMode -> Bool # (<=) :: BufferMode -> BufferMode -> Bool # (>) :: BufferMode -> BufferMode -> Bool # (>=) :: BufferMode -> BufferMode -> Bool # max :: BufferMode -> BufferMode -> BufferMode # min :: BufferMode -> BufferMode -> BufferMode # | |
Read BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types readsPrec :: Int -> ReadS BufferMode # readList :: ReadS [BufferMode] # readPrec :: ReadPrec BufferMode # readListPrec :: ReadPrec [BufferMode] # | |
Show BufferMode | Since: base-4.2.0.0 |
Defined in GHC.IO.Handle.Types showsPrec :: Int -> BufferMode -> ShowS # show :: BufferMode -> String # showList :: [BufferMode] -> ShowS # |
hGetBuffering :: Handle -> Shell BufferMode Source #
Get the buffering mode of the given handle.
hSetBuffering :: Handle -> BufferMode -> Shell () Source #
Set the buffering mode of the given handle.
Text I/O
hPutStrLn :: Handle -> String -> Shell () Source #
Write a string to a handle, followed by a newline.
Terminal text formatting
background :: Color -> String -> String Source #
Apply the given background color to the given string.
highlight :: String -> String Source #
Apply the terminal's default highlighting to the given string.
ByteString I/O
hPutBytes :: Handle -> ByteString -> Shell () Source #
Write a ByteString
to a handle. Newline is not appended.
hGetByteLine :: Handle -> Shell ByteString Source #
Read a line of input from a handle and return it as a ByteString
.
hGetByteContents :: Handle -> Shell ByteString Source #
Read all remaining input from a handle and return it as a ByteString
.
Convenient re-exports
module System.FilePath
join :: Monad m => m (m a) -> m a #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
Examples
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
class Applicative m => Monad (m :: Type -> Type) where #
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Instances of Monad
should satisfy the following laws:
Furthermore, the Monad
and Applicative
operations should relate as follows:
The above laws imply:
and that pure
and (<*>
) satisfy the applicative functor laws.
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
(>>=) :: m a -> (a -> m b) -> m b infixl 1 #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
(>>) :: m a -> m b -> m b infixl 1 #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
Inject a value into the monadic type.
Fail with a message. This operation is not part of the
mathematical definition of a monad, but is invoked on pattern-match
failure in a do
expression.
As part of the MonadFail proposal (MFP), this function is moved
to its own class MonadFail
(see Control.Monad.Fail for more
details). The definition here will be removed in a future
release.
Instances
Monad [] | Since: base-2.1 |
Monad Maybe | Since: base-2.1 |
Monad IO | Since: base-2.1 |
Monad Par1 | Since: base-4.9.0.0 |
Monad Q | |
Monad STM | Since: base-4.3.0.0 |
Monad ReadPrec | Since: base-2.1 |
Monad ReadP | Since: base-2.1 |
Monad NonEmpty | Since: base-4.9.0.0 |
Monad P | Since: base-2.1 |
Monad Shell Source # | |
Monad (Either e) | Since: base-4.4.0.0 |
Monad (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monoid a => Monad ((,) a) | Since: base-4.9.0.0 |
Monad f => Monad (Rec1 f) | Since: base-4.9.0.0 |
(Monad m, Error e) => Monad (ErrorT e m) | |
Monad ((->) r :: Type -> Type) | Since: base-2.1 |
(Monad f, Monad g) => Monad (f :*: g) | Since: base-4.9.0.0 |
Monad f => Monad (M1 i c f) | Since: base-4.9.0.0 |
class Functor (f :: Type -> Type) where #
The Functor
class is used for types that can be mapped over.
Instances of Functor
should satisfy the following laws:
fmap id == id fmap (f . g) == fmap f . fmap g
The instances of Functor
for lists, Maybe
and IO
satisfy these laws.
Instances
Functor [] | Since: base-2.1 |
Functor Maybe | Since: base-2.1 |
Functor IO | Since: base-2.1 |
Functor Par1 | Since: base-4.9.0.0 |
Functor Q | |
Functor Handler | Since: base-4.6.0.0 |
Functor STM | Since: base-4.3.0.0 |
Functor ReadPrec | Since: base-2.1 |
Functor ReadP | Since: base-2.1 |
Functor NonEmpty | Since: base-4.9.0.0 |
Functor P | Since: base-4.8.0.0 |
Defined in Text.ParserCombinators.ReadP | |
Functor Shell Source # | |
Functor (Either a) | Since: base-3.0 |
Functor (V1 :: Type -> Type) | Since: base-4.9.0.0 |
Functor (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Functor ((,) a) | Since: base-2.1 |
Monad m => Functor (Handler m) | |
Functor f => Functor (Rec1 f) | Since: base-4.9.0.0 |
Functor (URec Char :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Double :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Float :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Int :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec Word :: Type -> Type) | Since: base-4.9.0.0 |
Functor (URec (Ptr ()) :: Type -> Type) | Since: base-4.9.0.0 |
Functor m => Functor (ErrorT e m) | |
Functor ((->) r :: Type -> Type) | Since: base-2.1 |
Functor (K1 i c :: Type -> Type) | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :+: g) | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :*: g) | Since: base-4.9.0.0 |
Functor f => Functor (M1 i c f) | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :.: g) | Since: base-4.9.0.0 |
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
replicateM_ :: Applicative m => Int -> m a -> m () #
Like replicateM
, but discards the result.
replicateM :: Applicative m => Int -> m a -> m [a] #
performs the action replicateM
n actn
times,
gathering the results.
foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m () #
Like foldM
, but discards the result.
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b #
The foldM
function is analogous to foldl
, except that its result is
encapsulated in a monad. Note that foldM
works from left-to-right over
the list arguments. This could be an issue where (
and the `folded
function' are not commutative.>>
)
foldM f a1 [x1, x2, ..., xm] == do a2 <- f a1 x1 a3 <- f a2 x2 ... f am xm
If right-to-left evaluation is required, the input list should be reversed.
zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () #
zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c] #
mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c]) #
The mapAndUnzipM
function maps its first argument over a list, returning
the result as a pair of lists. This function is mainly used with complicated
data structures or a state-transforming monad.
forever :: Applicative f => f a -> f b #
Repeat an action indefinitely.
Examples
A common use of forever
is to process input from network sockets,
Handle
s, and channels
(e.g. MVar
and
Chan
).
For example, here is how we might implement an echo
server, using
forever
both to listen for client connections on a network socket
and to echo client input on client connection handles:
echoServer :: Socket -> IO () echoServer socket =forever
$ do client <- accept socketforkFinally
(echo client) (\_ -> hClose client) where echo :: Handle -> IO () echo client =forever
$ hGetLine client >>= hPutStrLn client
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right composition of Kleisli arrows.
filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a] #
This generalizes the list-based filter
function.
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) #
sequence_ :: (Foldable t, Monad m) => t (m a) -> m () #
Evaluate each monadic action in the structure from left to right,
and ignore the results. For a version that doesn't ignore the
results see sequence
.
As of base 4.8.0.0, sequence_
is just sequenceA_
, specialized
to Monad
.
void :: Functor f => f a -> f () #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing>>>
void (Just 3)
Just ()
Replace the contents of an
with unit,
resulting in an Either
Int
Int
:Either
Int
'()'
>>>
void (Left 8675309)
Left 8675309>>>
void (Right 8675309)
Right ()
Replace every element of a list with unit:
>>>
void [1,2,3]
[(),(),()]
Replace the second element of a pair with unit:
>>>
void (1,2)
(1,())
Discard the result of an IO
action:
>>>
mapM print [1,2]
1 2 [(),()]>>>
void $ mapM print [1,2]
1 2
liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r #
Promote a function to a monad, scanning the monadic arguments from
left to right (cf. liftM2
).
liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r #
Promote a function to a monad, scanning the monadic arguments from left to right. For example,
liftM2 (+) [0,1] [0,2] = [0,2,1,3] liftM2 (+) (Just 1) Nothing = Nothing
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #
Same as >>=
, but with the arguments interchanged.
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
Monads that also support choice and failure.
Nothing
The identity of mplus
. It should also satisfy the equations
mzero >>= f = mzero v >> mzero = mzero
The default definition is
mzero = empty
An associative operation. The default definition is
mplus = (<|>
)
Instances
MonadPlus [] | Since: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
MonadPlus IO | Since: base-4.9.0.0 |
MonadPlus STM | Since: base-4.3.0.0 |
MonadPlus ReadPrec | Since: base-2.1 |
MonadPlus ReadP | Since: base-2.1 |
MonadPlus P | Since: base-2.1 |
Defined in Text.ParserCombinators.ReadP | |
MonadPlus (U1 :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus f => MonadPlus (Rec1 f) | Since: base-4.9.0.0 |
(Monad m, Error e) => MonadPlus (ErrorT e m) | |
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) | Since: base-4.9.0.0 |
MonadPlus f => MonadPlus (M1 i c f) | Since: base-4.9.0.0 |