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

Safe HaskellNone

Control.Shell

Description

Simple interface for shell scripting-like tasks.

Synopsis

Documentation

data Shell a Source

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

class Guard guard a | guard -> a whereSource

Methods

guard :: String -> guard -> Shell aSource

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 () 
Guard (Maybe a) a 
Guard a b => Guard (Shell a) b 

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

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

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

Perform an action that may fail without aborting the entire computation. Forces serialization.

orElse :: Shell a -> Shell a -> Shell aSource

Attempt to run the first command. If the first command fails, run the second. Forces serialization of the first command.

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

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.

getEnv :: String -> Shell StringSource

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

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

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

run :: FilePath -> [String] -> String -> Shell StringSource

Execute an external command. No globbing, escaping or other external shell magic is performed on either the command or arguments. The program's text output 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.

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

Run an interactive process.

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

Run a program and return a boolean indicating whether the command succeeded, the output from stdout, and the output from stderr. This command will never fail.

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

Run a command with elevated privileges.

cd :: FilePath -> Shell ()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 :: Shell FilePathSource

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 aSource

Execute a command in the given working directory, then restore the previous working directory.

isDirectory :: FilePath -> Shell BoolSource

Does the given path lead to a directory?

withHomeDirectory :: (FilePath -> Shell a) -> Shell aSource

Do something with the user's home directory.

inHomeDirectory :: Shell a -> Shell aSource

Do something *in* the user's home directory.

withAppDirectory :: String -> (FilePath -> Shell a) -> Shell aSource

Do something with the given application's data directory.

inAppDirectory :: FilePath -> Shell a -> Shell aSource

Do something *in* the given application's data 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.

cpFiltered :: (FilePath -> Bool) -> FilePath -> FilePath -> Shell ()Source

Recursively copy a directory, but omit all files that do not match the give predicate.

isFile :: FilePath -> Shell BoolSource

Does the given path lead to a file?

rm :: FilePath -> Shell ()Source

Remove a file.

mv :: FilePath -> FilePath -> Shell ()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.

file :: File a => FilePath -> aSource

withTempFile :: String -> (FilePath -> Handle -> Shell a) -> Shell aSource

Create a temp file in the standard system temp directory, do something with it, then remove it.

withCustomTempFile :: FilePath -> (FilePath -> Handle -> Shell a) -> Shell aSource

Create a temp file in the standard system temp directory, do something with it, then remove it.

withTempDirectory :: String -> (FilePath -> Shell a) -> Shell aSource

Create a temp directory in the standard system temp directory, do something with it, then remove it.

withCustomTempDirectory :: FilePath -> (FilePath -> Shell a) -> Shell aSource

Create a temp directory in given directory, do something with it, then remove it.

inTempDirectory :: Shell a -> Shell aSource

Performs a command inside a temporary directory. The directory will be cleaned up after the command finishes.

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

IO.hPutStr lifted into Shell for convenience.

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

IO.hPutStrLn lifted into Shell for convenience.

echo :: String -> Shell ()Source

putStrLn lifted into Shell for convenience.

(|>) :: Shell String -> (String -> Shell a) -> Shell aSource

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

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

Lift a computation from the IO monad.