shellmate-0.3.4.1: Simple interface for shell scripting in Haskell.

Safe HaskellNone
LanguageHaskell2010

Control.Shell

Contents

Description

Simple interface for shell scripting-like tasks.

Synopsis

Running Shell programs

data Shell a Source #

A shell command: either an IO computation or a pipeline of at least one step.

Instances

Monad Shell Source # 

Methods

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

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

return :: a -> Shell a #

fail :: String -> Shell a #

Functor Shell Source # 

Methods

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

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

Applicative Shell Source # 

Methods

pure :: a -> Shell a #

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

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

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

Guard a => Guard (Shell a) Source # 

Associated Types

type Result (Shell a) :: * Source #

Methods

assert :: String -> Shell a -> Shell (Result (Shell a)) Source #

type Result (Shell a) Source # 
type Result (Shell a) = Result a

data ExitReason Source #

Why did the computation terminate?

Constructors

Success 
Failure !String 

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.

exit :: Shell a Source #

Terminate the program successfully.

class Guard guard where Source #

Minimal complete definition

assert

Associated Types

type Result guard Source #

The type of the guard's return value, if it succeeds.

Methods

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.

Instances

Guard Bool Source # 

Associated Types

type Result Bool :: * Source #

Guard (Maybe a) Source # 

Associated Types

type Result (Maybe a) :: * Source #

Methods

assert :: String -> Maybe a -> Shell (Result (Maybe a)) Source #

Guard a => Guard (Shell a) Source # 

Associated Types

type Result (Shell a) :: * Source #

Methods

assert :: String -> Shell a -> Shell (Result (Shell a)) Source #

Guard (Either l r) Source # 

Associated Types

type Result (Either l r) :: * Source #

Methods

assert :: String -> Either l r -> Shell (Result (Either l r)) Source #

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.

cmdline :: [String] Source #

The executable's command line arguments.

Running external commands

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 #

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

Methods

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

data Env Source #

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.

Constructors

Env 

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.

sudo :: FilePath -> [String] -> Shell () Source #

Run a command with elevated privileges.

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.

shellEnv :: IO Env Source #

Get the current global shell environment, including standard input, output and error handles. Only safe to call within a computation lifted into Shell by liftIO.

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.

pwd :: Shell FilePath Source #

Get the current working directory.

ls :: FilePath -> Shell [FilePath] Source #

List the contents of a directory, sans . and ...

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.

isDirectory :: FilePath -> Shell Bool Source #

Does the given path lead to a 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

isFile :: FilePath -> Shell Bool Source #

Does the given path lead to a file?

rm :: FilePath -> Shell () Source #

Remove a file.

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.

input :: FilePath -> Shell String Source #

Lazily read a file.

output :: FilePath -> String -> Shell () Source #

Lazily write a file.

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.

openFile :: FilePath -> IOMode -> Shell Handle Source #

Open a file, returning a handle to it.

openBinaryFile :: FilePath -> IOMode -> Shell Handle Source #

Open a file in binary mode, returning a handle to it.

Working with temporary files and directories

data FileMode Source #

Perform a file operation in binary or text mode?

Constructors

BinaryMode 
TextMode 

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

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 

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.

Constructors

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 n items if the argument is Just n and is otherwise implementation-dependent.

hFlush :: Handle -> Shell () Source #

Flush a handle.

hClose :: Handle -> Shell () Source #

Close a handle.

hReady :: Handle -> Shell Bool Source #

Is the handle ready for reading?

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.

getStdIn :: Shell Handle Source #

Get the standard input, output and error handle respectively.

getStdOut :: Shell Handle Source #

Get the standard input, output and error handle respectively.

getStdErr :: Shell Handle Source #

Get the standard input, output and error handle respectively.

Text I/O

hPutStr :: Handle -> String -> Shell () Source #

Write a string to a handle.

hPutStrLn :: Handle -> String -> Shell () Source #

Write a string to a handle, followed by a newline.

echo :: String -> Shell () Source #

Write a string to standard output, followed by a newline.

echo_ :: String -> Shell () Source #

Write a string to standard output, without appending a newline.

ask :: Shell String Source #

Read a line of text from standard input.

stdin :: Shell String Source #

Get the contents of the computation's standard input.

hGetLine :: Handle -> Shell String Source #

Read a line of input from a handle.

hGetContents :: Handle -> Shell String Source #

Lazily read all remaining input from a handle.

Terminal text formatting

color :: Color -> String -> String Source #

Apply the given color to the given string.

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.

bold :: String -> String Source #

Output the given string in bold font.

underline :: String -> String Source #

Underline the given string.

ByteString I/O

hGetBytes :: Handle -> Int -> Shell ByteString Source #

Read n bytes from a handle.

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