coquina-0.1.0.0: Yet another shell monad.

Safe HaskellNone
LanguageHaskell2010

Coquina

Contents

Description

Coquina provides a convenient interface for running shell commands in Haskell. The core functionality of Coquina is the ability to run a sequence of Shell operations, inspect the output of each operation, combine their results (i.e., their exit codes, stdout, and stderr), and stop execution if one of them fails. See the readme for an example.

Synopsis

The Shell Monad

class Monad m => MonadShell m where Source #

A class that supports reading and writing stdout and stderr

Methods

tellOutput :: (Text, Text) -> m () Source #

readOutput :: m a -> m ((Text, Text), a) Source #

Instances
Monad m => MonadShell (Shell m) Source # 
Instance details

Defined in Coquina

Methods

tellOutput :: (Text, Text) -> Shell m () Source #

readOutput :: Shell m a -> Shell m ((Text, Text), a) Source #

tellStdout :: MonadShell m => Text -> m () Source #

Write to stdout

tellStderr :: MonadShell m => Text -> m () Source #

Write to stderr

readStdout :: MonadShell m => m a -> m (Text, a) Source #

Read the stdout of a command

readStderr :: MonadShell m => m a -> m (Text, a) Source #

Read the stderr of a command

newtype Shell m a Source #

An action that supports running commands, reading their output, and emitting output

Constructors

Shell 

Fields

Instances
MonadTrans Shell Source # 
Instance details

Defined in Coquina

Methods

lift :: Monad m => m a -> Shell m a #

MonadWriter w m => MonadWriter w (Shell m) Source # 
Instance details

Defined in Coquina

Methods

writer :: (a, w) -> Shell m a #

tell :: w -> Shell m () #

listen :: Shell m a -> Shell m (a, w) #

pass :: Shell m (a, w -> w) -> Shell m a #

Monad m => MonadError Int (Shell m) Source # 
Instance details

Defined in Coquina

Methods

throwError :: Int -> Shell m a #

catchError :: Shell m a -> (Int -> Shell m a) -> Shell m a #

Monad m => Monad (Shell m) Source # 
Instance details

Defined in Coquina

Methods

(>>=) :: Shell m a -> (a -> Shell m b) -> Shell m b #

(>>) :: Shell m a -> Shell m b -> Shell m b #

return :: a -> Shell m a #

fail :: String -> Shell m a #

Functor m => Functor (Shell m) Source # 
Instance details

Defined in Coquina

Methods

fmap :: (a -> b) -> Shell m a -> Shell m b #

(<$) :: a -> Shell m b -> Shell m a #

Monad m => Applicative (Shell m) Source # 
Instance details

Defined in Coquina

Methods

pure :: a -> Shell m a #

(<*>) :: Shell m (a -> b) -> Shell m a -> Shell m b #

liftA2 :: (a -> b -> c) -> Shell m a -> Shell m b -> Shell m c #

(*>) :: Shell m a -> Shell m b -> Shell m b #

(<*) :: Shell m a -> Shell m b -> Shell m a #

MonadIO m => MonadIO (Shell m) Source # 
Instance details

Defined in Coquina

Methods

liftIO :: IO a -> Shell m a #

MonadThrow m => MonadThrow (Shell m) Source # 
Instance details

Defined in Coquina

Methods

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

MonadCatch m => MonadCatch (Shell m) Source # 
Instance details

Defined in Coquina

Methods

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

MonadMask m => MonadMask (Shell m) Source # 
Instance details

Defined in Coquina

Methods

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

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

generalBracket :: Shell m a -> (a -> ExitCase b -> Shell m c) -> (a -> Shell m b) -> Shell m (b, c) #

MonadLogger m => MonadLogger (Shell m) Source # 
Instance details

Defined in Coquina

Methods

monadLoggerLog :: ToLogStr msg => Loc -> LogSource -> LogLevel -> msg -> Shell m () #

Monad m => MonadShell (Shell m) Source # 
Instance details

Defined in Coquina

Methods

tellOutput :: (Text, Text) -> Shell m () Source #

readOutput :: Shell m a -> Shell m ((Text, Text), a) Source #

runShell :: Monad m => Shell m a -> m (Text, Text, Either Int a) Source #

Run a shell action, producing stdout, stderr, and a result.

execShell :: Monad m => Shell m a -> m (ExitCode, Text, Text) Source #

Run a shell action, producing an exit code, stdout, and stderr

hoistShell :: (forall x. m x -> n x) -> Shell m a -> Shell n a Source #

Hoist a shell action into another monad

Constructing Shell actions

shellCreateProcessWith :: MonadIO m => (CreateProcess -> IO (ExitCode, Text, Text)) -> CreateProcess -> Shell m () Source #

Run a shell process using the given runner function

shellCreateProcessWithEnv :: MonadIO m => Map String String -> CreateProcess -> Shell m () Source #

Run a shell process with the given environment variables added to the existing environment

runCreateProcess :: CreateProcess -> IO (ExitCode, Text, Text) Source #

Execute a shell process

runCreateProcessWithEnv :: Map String String -> CreateProcess -> IO (ExitCode, Text, Text) Source #

Execute a shell process with environment variables

shellCreateProcessWithStdOut :: MonadIO m => Handle -> CreateProcess -> Shell m () Source #

Run a shell process with stdout directed to the provided handle

Running in a temporary directory

inTempDirectory :: MonadIO m => String -> (FilePath -> Shell IO a) -> Shell m a Source #

Run a shell command with access to a temporary directory

Streamable Shell processes

data StreamingProcess m Source #

Represents a process that is running and whose incremental output can be retrieved before it completes. The _streamingProcess_waitForProcess finalizer can be called to get the exit status of the process and to get the final output.

Instances
Generic (StreamingProcess m) Source # 
Instance details

Defined in Coquina

Associated Types

type Rep (StreamingProcess m) :: Type -> Type #

type Rep (StreamingProcess m) Source # 
Instance details

Defined in Coquina

type Rep (StreamingProcess m) = D1 (MetaData "StreamingProcess" "Coquina" "coquina-0.1.0.0-inplace" False) (C1 (MetaCons "StreamingProcess" PrefixI True) (S1 (MetaSel (Just "_streamingProcess_waitForProcess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Shell m ExitCode)) :*: (S1 (MetaSel (Just "_streamingProcess_terminateProcess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Shell m ())) :*: S1 (MetaSel (Just "_streamingProcess_getProcessExitCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Shell m (Maybe ExitCode))))))

shellStreamableProcess Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> (ByteString -> IO ())

Handle stdout

-> (ByteString -> IO ())

Handle stderr

-> CreateProcess 
-> Shell m (StreamingProcess m) 

A process whose output can be inspected while it is still running.

shellStreamableProcessBuffered Source #

Arguments

:: (MonadIO m, MonadMask m) 
=> CreateProcess 
-> Shell m (StreamingProcess m, IO ByteString, IO ByteString)

(StreamingProcess, stdout, stderr)

Like shellStreamableProcess but instead of taking handlers for each stream, it automatically buffers the output of each stream and returns IO actions to read and clear the buffer.

Miscellaneous

logCommand :: CreateProcess -> IO () Source #

Print a shell command

showCommand :: CreateProcess -> String Source #

Convert a shell command to a string