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

Safe HaskellNone
LanguageHaskell98

Control.Shell

Contents

Description

Simple interface for shell scripting-like tasks.

Synopsis

Running Shell programs

data Shell a Source

Monad for running shell commands. If a command fails, the entire computation is aborted unless mayFail is used.

shell :: Shell a -> IO (Either ExitReason a) Source

Run a Shell computation. The program's working directory and environment will be restored after after the computation finishes.

shell_ :: Shell a -> IO () Source

Run a shell computation and discard its return value. If the computation fails, print its error message to stderr and exit.

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 String -> (String -> Shell a) -> Shell a infixl 1 Source

Lazy counterpart to monadic bind. To stream data from a command a to a command b, do 'a |> b'.

try :: Shell a -> Shell (Either String a) Source

Perform an action that may fail without aborting the entire computation. Forces serialization. If the inner computation terminates successfully, the outer computation terminates as well.

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 a computation, successfully.

class Guard guard where Source

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 :: 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.

when :: Guard g => g -> Shell a -> Shell () Source

Perform the given computation if the given guard passes, otherwise do nothing.

unless :: Guard g => g -> Shell a -> Shell () Source

Perform the given computation if the given guard fails, otherwise do nothing.

Environment handling

setEnv :: MonadIO m => String -> String -> m () Source

Set an environment variable.

getEnv :: String -> Shell String Source

Get the value of an environment variable. Returns the empty string if the variable doesn't exist.

withEnv :: String -> (String -> String) -> Shell a -> Shell a Source

Run a computation with a new value for an environment variable. Note that this will *not* affect external commands spawned using liftIO or which directory is considered the system temp directory.

lookupEnv :: String -> Shell (Maybe String) Source

Get the value of an environment variable. Returns Nothing if the variable doesn't exist.

cmdline :: [String] Source

The executable's command line arguments.

Running 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:

Methods

liftIO :: IO a -> m a

Lift a computation from the IO monad.

Instances

MonadIO IO 
MonadIO Shell 
MonadIO m => MonadIO (IdentityT m) 
MonadIO m => MonadIO (ReaderT r m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (StateT s m) 
(Error e, MonadIO m) => MonadIO (ErrorT e m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

run :: FilePath -> [String] -> String -> Shell String 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 returned, and not echoed to the screen.

run_ :: FilePath -> [String] -> String -> Shell () Source

Like run, but echoes the command's text output to the screen instead of returning it.

genericRun :: FilePath -> [String] -> String -> Shell (Int, String, String) Source

Like run, but always succeeds and returns the program's standard error stream and exit code.

runInteractive :: FilePath -> [String] -> Shell () Source

Run an interactive process.

sudo :: FilePath -> [String] -> String -> Shell String Source

Run a command with elevated privileges.

Working with directories

cd :: MonadIO m => FilePath -> m () Source

Change working directory.

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 :: MonadIO m => m FilePath Source

Get the current working directory.

ls :: FilePath -> Shell [FilePath] Source

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

mkdir :: MonadIO m => Bool -> FilePath -> m () Source

Create a directory. Optionally create any required missing directories as well.

rmdir :: MonadIO m => FilePath -> m () 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 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 :: MonadIO m => FilePath -> m () Source

Remove a file.

mv :: MonadIO m => FilePath -> FilePath -> m () Source

Rename a file.

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 :: MonadIO m => FilePath -> String -> m () Source

Lazily write a file.

Working with temporary files and directories

withTempFile :: String -> (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 :: 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 :: String -> (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.

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

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.

hFlush :: Handle -> Shell () Source

Flush a handle.

hClose :: Handle -> Shell () Source

Close a handle.

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.

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 :: MonadIO m => String -> m () Source

Write a string to stdout followed by a newline.

ask :: Shell String Source

Read one line of input from stdin.

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.

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