shh-0.4.0.1: Simple shell scripting from Haskell

Safe HaskellNone
LanguageHaskell2010

Shh

Description

Shh provides a shell-like environment for Haskell.

Synopsis

Documentation

initInteractive :: IO () Source #

This function needs to be called in order to use the library successfully from GHCi. If you use the formatPrompt function from the shh-extras package, this will be automatically called for you.

Constructing a Proc

| === External Processes These allow for the construction of Procs that call external processes. You will often use the TemplateHaskell functions below to create these.

exe :: (Unit a, ExecArgs a) => String -> a Source #

Execute the given command. Further arguments can be passed in.

exe "ls" "-l"

See also loadExe and loadEnv.

mkProc :: String -> [String] -> Proc () Source #

Create a Proc from a command and a list of arguments. Does not delegate control-c handling.

mkProc' :: Bool -> String -> [String] -> Proc () Source #

Create a Proc from a command and a list of arguments. The boolean represents whether we should delegate control-c or not. Most uses of mkProc' in Shh do not delegate control-c.

runProc :: Proc a -> IO a Source #

Run's a Proc in IO. This is usually not required, as most commands in Shh are polymorphic in their return type, and work just fine in IO directly.

data Proc a Source #

Type representing a series or pipeline (or both) of shell commands.

Proc's can communicate to each other via stdin, stdout and stderr and can communicate to Haskell via their parameterised return type, or by throwing an exception.

Instances
Monad Proc Source # 
Instance details

Defined in Shh.Internal

Methods

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

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

return :: a -> Proc a #

fail :: String -> Proc a #

Functor Proc Source # 
Instance details

Defined in Shh.Internal

Methods

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

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

Applicative Proc Source # 
Instance details

Defined in Shh.Internal

Methods

pure :: a -> Proc a #

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

liftA2 :: (a -> b -> c) -> Proc a -> Proc b -> Proc c #

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

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

MonadIO Proc Source # 
Instance details

Defined in Shh.Internal

Methods

liftIO :: IO a -> Proc a #

ProcFailure Proc Source # 
Instance details

Defined in Shh.Internal

PipeResult Proc Source # 
Instance details

Defined in Shh.Internal

Methods

(|>) :: Proc b -> Proc a -> Proc a Source #

(|!>) :: Proc b -> Proc a -> Proc a Source #

(&>) :: Proc a -> Stream -> Proc a Source #

(&!>) :: Proc a -> Stream -> Proc a Source #

nativeProc :: NFData a => (Handle -> Handle -> Handle -> IO a) -> Proc a Source #

Semigroup (Proc a) Source #

The Semigroup instance for Proc pipes the stdout of one process into the stdin of the next. However, consider using |> instead which behaves when used in an IO context. If you use <> in an IO monad you will be using the IO instance of semigroup which is a sequential execution. |> prevents that error.

Instance details

Defined in Shh.Internal

Methods

(<>) :: Proc a -> Proc a -> Proc a #

sconcat :: NonEmpty (Proc a) -> Proc a #

stimes :: Integral b => b -> Proc a -> Proc a #

a ~ () => Monoid (Proc a) Source # 
Instance details

Defined in Shh.Internal

Methods

mempty :: Proc a #

mappend :: Proc a -> Proc a -> Proc a #

mconcat :: [Proc a] -> Proc a #

ExecArgs (Proc ()) Source # 
Instance details

Defined in Shh.Internal

Methods

toArgs :: [String] -> Proc () Source #

Native Processes

You can also create native Haskell Procs which behave the same way, but simply run Haskell functions instead of external processes.

NB: The functions here that operate on Strings from stdin read them lazily, and can be used in a streaming fashion.

pureProc :: PipeResult io => (String -> String) -> io () Source #

Creates a pure Proc that simple transforms the stdin and writes it to stdout. The input can be infinite.

>>> yes |> pureProc (take 4) |> capture
"y\ny\n"

writeOutput :: PipeResult io => String -> io () Source #

Simple Proc that writes a String to it's stdout. This behaves very much like the standard echo utility, except that there is no restriction as to what can be in the string argument.

>>> writeOutput "Hello"
Hello

writeError :: PipeResult io => String -> io () Source #

Simple Proc that writes a String to it's stderr. See also writeOutput. >>> writeError Hello &> devNull Hello

prefixLines :: PipeResult io => String -> io () Source #

Captures the stdout of a process and prefixes all the lines with the given string.

>>> some_command |> prefixLines "stdout: " |!> prefixLines "stderr: " &> StdErr
stdout: this is stdout
stderr: this is stderr

capture :: PipeResult io => io String Source #

A special Proc which captures it's stdin and presents it as a String to Haskell.

>>> printf "Hello" |> md5sum |> capture
"8b1a9953c4611296a827abf8c47804d7  -\n"

captureTrim :: PipeResult io => io String Source #

Like capture, except that it trims leading and trailing white space.

>>> printf "Hello" |> md5sum |> captureTrim
"8b1a9953c4611296a827abf8c47804d7  -"

captureSplit :: PipeResult io => String -> io [String] Source #

Like capture, but splits the input using the provided separator.

NB: This is strict. If you want a streaming version, use readInput

readInput :: (NFData a, PipeResult io) => (String -> IO a) -> io a Source #

Simple Proc that reads it's input, and can react to it with an IO action. Does not write anything to it's output. See also capture.

readInput uses lazy IO to read it's stdin, and works with infinite inputs.

>>> yes |> readInput (pure . unlines . take 3 . lines)
"y\ny\ny\n"

readInputSplit :: (NFData a, PipeResult io) => String -> ([String] -> IO a) -> io a Source #

Like readInput, but splits the string.

>>> yes |> readInputSplit "\n" (pure . take 3)
["y","y","y"]

readInputSplit0 :: (NFData a, PipeResult io) => ([String] -> IO a) -> io a Source #

Like readInput, but splits the string on the 0 byte.

>>> writeOutput "1\0\&2\0" |> readInputSplit0 pure
["1","2"]

readInputLines :: (NFData a, PipeResult io) => ([String] -> IO a) -> io a Source #

Like readInput, but splits the string on new lines.

>>> writeOutput "a\nb\n" |> readInputLines pure
["a","b"]

readInputP :: (NFData a, PipeResult io) => (String -> Proc a) -> io a Source #

Simple Proc that reads it's input and can react to the output by calling other Proc's which can write something to it's stdout. The internal Proc is given devnull as it's input.

readInputSplitP :: (NFData a, PipeResult io) => String -> ([String] -> Proc a) -> io a Source #

Like readInputP, but splits the input.

readInputSplit0P :: (NFData a, PipeResult io) => ([String] -> Proc a) -> io a Source #

Like readInputP, but splits the input on 0 bytes.

readInputLinesP :: (NFData a, PipeResult io) => ([String] -> Proc a) -> io a Source #

Like readInputP, but splits the input on new lines.

xargs1 :: (NFData a, Monoid a) => String -> (String -> Proc a) -> Proc a Source #

xargs1 n f runs f for each item in the input separated by n. Similar to the standard xargs utility, but you get to choose the separator, and it only does one argument per command. Compare the following two lines, which do the same thing.

>>> printf "a\\0b" |> xargs "--null" "-L1" "echo" |> cat
a
b
>>> printf "a\\0b" |> xargs1 "\0" echo |> cat
a
b

One benefit of this method over the standard xargs is that we can run Haskell functions as well.

>>> yes |> head "-n" 5 |> xargs1 "\n" (const $ pure $ Sum 1)
Sum {getSum = 5}

Piping and Redirection

class PipeResult f where Source #

This class is used to allow most of the operators in Shh to be polymorphic in their return value. This makes using them in an IO context easier (we can avoid having to prepend everything with a runProc).

Methods

(|>) :: Proc b -> Proc a -> f a infixl 1 Source #

Use this to send the output of on process into the input of another. This is just like a shells `|` operator.

The result is polymorphic in it's output, and can result in either another `Proc a` or an `IO a` depending on the context in which it is used.

If any intermediate process throws an exception, the whole pipeline is canceled.

The result of the last process in the chain is the result returned by the pipeline.

>>> echo "Hello" |> wc
      1       1       6

(|!>) :: Proc b -> Proc a -> f a infixl 1 Source #

Similar to |!> except that it connects stderr to stdin of the next process in the chain.

NB: The next command to be |> on will recapture the stdout of both preceding processes, because they are both going to the same handle!

See the &> and &!> operators for redirection.

>>> echo "Ignored" |!> wc "-c"
Ignored
0

(&>) :: Proc a -> Stream -> f a infixl 9 Source #

Redirect stdout of this process to another location

>>> echo "Ignore me" &> Append "/dev/null"

(&!>) :: Proc a -> Stream -> f a infixl 9 Source #

Redirect stderr of this process to another location

>>> echo "Shh" &!> StdOut
Shh

nativeProc :: NFData a => (Handle -> Handle -> Handle -> IO a) -> f a Source #

Lift a Haskell function into a Proc. The handles are the stdin stdout and stderr of the resulting Proc

Instances
PipeResult IO Source # 
Instance details

Defined in Shh.Internal

Methods

(|>) :: Proc b -> Proc a -> IO a Source #

(|!>) :: Proc b -> Proc a -> IO a Source #

(&>) :: Proc a -> Stream -> IO a Source #

(&!>) :: Proc a -> Stream -> IO a Source #

nativeProc :: NFData a => (Handle -> Handle -> Handle -> IO a) -> IO a Source #

PipeResult Proc Source # 
Instance details

Defined in Shh.Internal

Methods

(|>) :: Proc b -> Proc a -> Proc a Source #

(|!>) :: Proc b -> Proc a -> Proc a Source #

(&>) :: Proc a -> Stream -> Proc a Source #

(&!>) :: Proc a -> Stream -> Proc a Source #

nativeProc :: NFData a => (Handle -> Handle -> Handle -> IO a) -> Proc a Source #

(<|) :: PipeResult f => Proc a -> Proc b -> f a infixr 1 Source #

Flipped version of |> with lower precedence.

>>> captureTrim <| (echo "Hello" |> wc "-c")
"6"

data Stream Source #

Type used to represent destinations for redirects. Truncate file is like > file in a shell, and Append file is like >> file.

devNull :: Stream Source #

Shortcut for Truncate "/dev/null"

>>> echo "Hello" &> devNull

Lazy/Streaming reads

These reads are lazy. The process is run long enough to produce the amount of output that is actually used. It is therefor suitable for use with infinite output streams. The process is terminated as soon the function finishes. Note that the result is forced to normal form to prevent any accidental reading after the process has terminated.

NB: See readInput and pureProc for more flexible options to those listed here.

withRead :: (PipeResult f, NFData b) => Proc a -> (String -> IO b) -> f b Source #

Run a process and capture it's output lazily. Once the continuation is completed, the handles are closed. However, the process is run until it naturally terminates in order to capture the correct exit code. Most utilities behave correctly with this (e.g. cat will terminate if you close the handle).

Same as p |> readInput f

withReadSplit0 :: (NFData b, PipeResult io) => Proc a -> ([String] -> IO b) -> io b Source #

Like withRead except it splits the string with split0 first.

withReadLines :: (NFData b, PipeResult io) => Proc a -> ([String] -> IO b) -> io b Source #

Like withRead except it splits the string with lines first.

NB: Please consider using withReadSplit0 where you can.

withReadWords :: (NFData b, PipeResult io) => Proc a -> ([String] -> IO b) -> io b Source #

Like withRead except it splits the string with words first.

Strict reads

NB: See also capture

readProc :: PipeResult io => Proc a -> io String Source #

Read the stdout of a Proc. This captures stdout, so further piping will not see anything on the input.

This is strict, so the whole output is read into a String. See withRead for a lazy version that can be used for streaming.

readTrim :: (Functor io, PipeResult io) => Proc a -> io String Source #

Like readProc, but trim leading and tailing whitespace.

readSplit0 :: Proc () -> IO [String] Source #

A convenience function for reading in a "\NUL" separated list of strings. This is commonly used when dealing with paths.

readSplit0 $ find "-print0"

readLines :: Proc () -> IO [String] Source #

A convenience function for reading the output lines of a Proc.

Note: Please consider using readSplit0 instead if you can.

readWords :: Proc () -> IO [String] Source #

Read output into a list of words

readAuto :: Read a => Proc () -> IO a Source #

Like readProc, but attempts to read the result.

Writing to stdin

NB: See also writeOutput for an echo-like option.

(<<<) :: PipeResult io => Proc a -> String -> io a Source #

Infix version of writeProc

(>>>) :: PipeResult io => String -> Proc a -> io a Source #

Flipped, infix version of writeProc

writeProc :: PipeResult io => Proc a -> String -> io a Source #

Provide the stdin of a Proc from a String

Same as writeOutput s |> p

readWriteProc :: MonadIO io => Proc a -> String -> io String Source #

Read and write to a Proc. Same as readProc proc <<< input

apply :: MonadIO io => Proc a -> String -> io String Source #

Some as readWriteProc. Apply a Proc to a String.

> apply md5sum "Hello"

"8b1a9953c4611296a827abf8c47804d7 -n"

String manipulation

Utility functions for dealing with common string issues in shell scripting.

trim :: String -> String Source #

Trim leading and tailing whitespace.

split0 :: String -> [String] Source #

Function that splits '\0' separated list of strings. Useful in conjunction with find . "-print0".

Exceptions

If any exception is allowed to propagate out of a pipeline, all the processes comprising the pipeline will be terminated. This is contrary to how a shell normally works (even with -o pipefail!).

data Failure Source #

When a process exits with a non-zero exit code we throw this Failure exception.

The only exception to this is when a process is terminated by SIGPIPE in a pipeline, in which case we ignore it.

Constructors

Failure 
Instances
Eq Failure Source # 
Instance details

Defined in Shh.Internal

Methods

(==) :: Failure -> Failure -> Bool #

(/=) :: Failure -> Failure -> Bool #

Ord Failure Source # 
Instance details

Defined in Shh.Internal

Show Failure Source # 
Instance details

Defined in Shh.Internal

Exception Failure Source # 
Instance details

Defined in Shh.Internal

ignoreFailure :: (Functor m, ProcFailure m) => Proc a -> m () Source #

Run a Proc action, ignoring any Failure exceptions. This can be used to prevent a process from interrupting a whole pipeline.

>>> false |> (sleep 2 >> echo 1)
*** Exception: Command `false` failed [exit 1]
>>> (ignoreFailure  false) |> (sleep 2 >> echo 1)
1

catchFailure :: ProcFailure m => Proc a -> m (Either Failure a) Source #

Run a Proc action, catching an Failure exceptions and returning them.

catchCode :: (Functor m, ProcFailure m) => Proc a -> m Int Source #

Run an Proc action returning the return code if an exception was thrown, and 0 if it wasn't.

Constructing Arguments

class ExecArg a where Source #

A class for things that can be converted to arguments on the command line. The default implementation is to use show.

Minimal complete definition

Nothing

Methods

asArg :: a -> [String] Source #

asArg :: Show a => a -> [String] Source #

asArgFromList :: [a] -> [String] Source #

asArgFromList :: Show a => [a] -> [String] Source #

Instances
ExecArg Char Source # 
Instance details

Defined in Shh.Internal

ExecArg Int Source # 
Instance details

Defined in Shh.Internal

ExecArg Integer Source # 
Instance details

Defined in Shh.Internal

ExecArg Word Source # 
Instance details

Defined in Shh.Internal

ExecArg a => ExecArg [a] Source # 
Instance details

Defined in Shh.Internal

Methods

asArg :: [a] -> [String] Source #

asArgFromList :: [[a]] -> [String] Source #

class ExecArgs a Source #

A class for building up a command

Minimal complete definition

toArgs

Instances
ExecArgs (IO ()) Source #

Commands can be executed directly in IO

Instance details

Defined in Shh.Internal

Methods

toArgs :: [String] -> IO () Source #

ExecArgs (Proc ()) Source # 
Instance details

Defined in Shh.Internal

Methods

toArgs :: [String] -> Proc () Source #

(ExecArg b, ExecArgs a) => ExecArgs (b -> a) Source # 
Instance details

Defined in Shh.Internal

Methods

toArgs :: [String] -> b -> a Source #

class Unit a Source #

Force a `()` result.

Instances
a ~ () => Unit (m a) Source # 
Instance details

Defined in Shh.Internal

Unit b => Unit (a -> b) Source # 
Instance details

Defined in Shh.Internal

Template Haskell helpers

encodeIdentifier :: String -> String Source #

Takes a string, and makes a Haskell identifier out of it. There is some chance of overlap. If the string is a path, the filename portion is used. The transformation replaces all non-alphanumeric characters with '_'. If the first character is uppercase it is forced into lowercase. If it starts with a number, it is prefixed with `_`. If it overlaps with a reserved word or a builtin, it is suffixed with an `_`.

data ExecReference Source #

Specify how executables should be referenced.

Constructors

Absolute

Find executables on PATH, but store their absolute path

SearchPath

Always search on PATH

load :: ExecReference -> [String] -> Q [Dec] Source #

Load the given executables into the program, checking their executability and creating a function missingExecutables to do a runtime check for their availability. Uses the encodeIdentifier function to create function names.

loadEnv :: ExecReference -> Q [Dec] Source #

Scans your '$PATH' environment variable and creates a function for each executable found. Binaries that would not create valid Haskell identifiers are encoded using the encodeIdentifier function.

loadFromDirs :: [FilePath] -> Q [Dec] Source #

Load executables from the given directories

loadFromBins :: [FilePath] -> Q [Dec] Source #

Load executables from the given directories appended with "/bin".

Useful for use with Nix.

loadAnnotated :: ExecReference -> (String -> String) -> [String] -> Q [Dec] Source #

Same as load, but allows you to modify the function names.

loadAnnotatedEnv :: ExecReference -> (String -> String) -> Q [Dec] Source #

Like loadEnv, but allows you to modify the function name that would be generated.

loadAnnotatedFromDirs :: [FilePath] -> (String -> String) -> Q [Dec] Source #

Load executables from the given dirs, applying the given transformation to the filenames.

loadExe :: ExecReference -> String -> Q [Dec] Source #

Create a function for the executable named

loadExeAs :: ExecReference -> String -> String -> Q [Dec] Source #

$(loadExeAs ref fnName executable) defines a function called fnName which executes the path in executable. If executable is an absolute path it is used directly. If it is just an executable name, then it is searched for in the PATH environment variable. If ref is SearchPath, the short name is retained, and your PATH will be searched at runtime. If ref is Absolute, a executable name will be turned into an absolute path, which will be used at runtime.

pathBins :: IO [FilePath] Source #

Get all executables on your `$PATH`.

pathBinsAbs :: IO [FilePath] Source #

Get all uniquely named executables on your `$PATH` as absolute file names. The uniqueness is determined by the filename, and not the whole path. First one found wins.

Builtins

cd :: Cd a => a Source #

Mimics the shell builtin "cd"