shh-0.7.2.1: Simple shell scripting from Haskell
Safe HaskellSafe-Inferred
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.

Running a Proc

class Shell 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

runProc :: HasCallStack => Proc a -> f a Source #

Instances

Instances details
Shell IO Source # 
Instance details

Defined in Shh.Internal

Methods

runProc :: HasCallStack => Proc a -> IO a Source #

Shell Proc Source # 
Instance details

Defined in Shh.Internal

Methods

runProc :: HasCallStack => Proc a -> Proc a Source #

Constructing a Proc

You usually don't need to runProc because most functions in shh are polymorphic in their return type. | === 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 :: (Command a, ExecArg str, HasCallStack) => str -> a Source #

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

exe "ls" "-l"

See also loadExe and loadEnv.

NB: It is recommended that you use the template haskell functions to load executables from your path. If you do it manually, it is recommended to use withFrozenCallStack from GHC.Stack

echo :: Cmd
echo = withFrozenCallStack (exe "echo")

mkProc :: HasCallStack => ByteString -> [ByteString] -> Proc () Source #

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

mkProcWith :: HasCallStack => ProcOptions -> ByteString -> [ByteString] -> Proc () Source #

Create a Proc with custom options.

data ProcOptions Source #

Options for making processes.

defaultProcOptions :: ProcOptions Source #

Default ProcOptions as used by most of this library.

delegateCtlc :: ProcOptions -> Bool Source #

Delegate control-c handling to the child.

closeFds :: ProcOptions -> Bool Source #

Close file descriptors before execing.

mkProc' :: HasCallStack => Bool -> ByteString -> [ByteString] -> Proc () Source #

Deprecated: Use mkProcWith instead

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.

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

Instances details
MonadIO Proc Source # 
Instance details

Defined in Shh.Internal

Methods

liftIO :: IO a -> 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 #

Functor Proc Source # 
Instance details

Defined in Shh.Internal

Methods

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

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

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 #

Shell Proc Source # 
Instance details

Defined in Shh.Internal

Methods

runProc :: HasCallStack => Proc a -> Proc a Source #

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 #

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 ~ () => Command (Proc a) Source # 
Instance details

Defined in Shh.Internal

Methods

toArgs :: [ByteString] -> Proc a Source #

Native Processes (Lazy)

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 lazy ByteStrings read from stdin, and can be used in a streaming fashion. 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 feeding process has it's stdout closed as soon the function finishes. Note that the result is forced to normal form to prevent any accidental reading after the process has terminated.

pureProc :: Shell io => (ByteString -> ByteString) -> io () Source #

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

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

writeOutput :: (ExecArg a, Shell io) => a -> io () Source #

Simple Proc that writes its argument to its stdout. This behaves very much like the standard printf utility, except that there is no restriction as to what can be in the argument.

NB: String arguments are encoded as UTF8, while ByteString is passed through. Be aware if you are using OverloadedStrings that you will get wrong results if using unicode in your string literal and it inferes anything other than String.

>>> writeOutput "Hello"
Hello

writeError :: (ExecArg a, Shell io) => a -> io () Source #

Simple Proc that writes its argument to its stderr. See also writeOutput.

>>> writeError "Hello" &> devNull
Hello

prefixLines :: Shell io => ByteString -> 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

readInput :: (NFData a, Shell io) => (ByteString -> IO a) -> io a Source #

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

readInput uses lazy IO to read its stdin, and works with infinite inputs.

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

readInputEndBy :: (NFData a, Shell io) => ByteString -> ([ByteString] -> IO a) -> io a Source #

Like readInput, but endBys the string.

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

readInputEndBy0 :: (NFData a, Shell io) => ([ByteString] -> IO a) -> io a Source #

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

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

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

Like readInput, but endBys the string on new lines.

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

readInputP :: (NFData a, Shell io) => (ByteString -> Proc a) -> io a Source #

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

readInputEndByP :: (NFData a, Shell io) => ByteString -> ([ByteString] -> Proc a) -> io a Source #

Like readInputP, but splits the input.

readInputEndBy0P :: (NFData a, Shell io) => ([ByteString] -> Proc a) -> io a Source #

Like readInputP, but splits the input on 0 bytes.

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

Like readInputP, but splits the input on new lines.

xargs1 :: (NFData a, Monoid a) => ByteString -> (ByteString -> 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}

Extracting output to Haskell (Strict)

These functions are trivially implemented in terms of the above. Note that they are strict.

capture :: Shell io => io ByteString Source #

A special Proc which captures its stdin and presents it as a ByteString to Haskell.

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

This is just readInput pure. Note that it is not lazy, and will read the entire ByteString into memory.

captureTrim :: Shell io => io ByteString Source #

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

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

captureEndBy :: Shell io => ByteString -> io [ByteString] Source #

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

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

captureEndBy0 :: Shell io => io [ByteString] Source #

Same as captureEndBy "\0".

captureLines :: Shell io => io [ByteString] Source #

Same as captureSplit "\n".

captureWords :: Shell io => io [ByteString] Source #

Capture stdout, splitting it into words.

Piping and Redirection

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

Use this to send the output of one process into the input of another. This is just like a shell's `|` operator.

The result is polymorphic in its 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

(|!>) :: Shell f => Proc a -> Proc b -> f b 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

pipe :: Shell f => Proc a -> Proc b -> f (a, b) Source #

Like |> except that it keeps both return results. Be aware that the fst element of this tuple may be hiding a SIGPIPE exception that will explode on you once you look at it.

You probably want to use |> unless you know you don't.

pipeErr :: Shell f => Proc a -> Proc b -> f (a, b) Source #

Like pipe, but plumbs stderr. See the warning in pipe.

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

Redirect stdout of this process to another location

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

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

Redirect stderr of this process to another location

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

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

Writing to stdin

NB: See also writeOutput for an echo-like option. These are all implemented in terms of writeOutput.

(<<<) :: Shell io => Proc a -> ByteString -> io a Source #

Infix version of writeProc

(>>>) :: Shell io => ByteString -> Proc a -> io a Source #

Flipped, infix version of writeProc

writeProc :: Shell io => Proc a -> ByteString -> io a Source #

Provide the stdin of a Proc from a ByteString

Same as writeOutput s |> p

apply :: (ExecArg a, Shell io) => Proc v -> a -> io ByteString Source #

Apply a Proc to a ByteString. That is, feed the bytestring to the stdin of the process and read the stdout.

> apply md5sum "Hello"

"8b1a9953c4611296a827abf8c47804d7 -n"

String manipulation

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

trim :: ByteString -> ByteString Source #

Trim leading and tailing whitespace.

>>> trim " a string \n"
"a string"

endBy :: ByteString -> ByteString -> [ByteString] Source #

Split a string separated by the provided separator. A trailing separator is ignored, and does not produce an empty string. Compatible with the output of most CLI programs, such as find -print0.

>>> endBy "\n" "a\nb\n"
["a","b"]
>>> endBy "\n" "a\nb"
["a","b"]
>>> endBy "\n" "a\nb\n\n"
["a","b",""]

endBy0 :: ByteString -> [ByteString] 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 

Fields

Instances

Instances details
Exception Failure Source # 
Instance details

Defined in Shh.Internal

Show Failure Source # 
Instance details

Defined in Shh.Internal

ignoreFailure :: (Functor m, Shell 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 "0.1" >> echo 1)
*** Exception: Command `false` failed [exit 1] at CallStack (from HasCallStack):
...
>>> (ignoreFailure false) |> (sleep "0.1" >> echo 1)
1

ignoreCode :: (Monad m, Shell m) => Int -> Proc a -> m () Source #

Run the Proc, but don't throw an exception if it exits with the given code. Note, that from this point on, if the proc did fail with the code, everything else now sees it as having exited with 0. If you need to know the code, you have to use exitCode.

tryFailure :: Shell m => Proc a -> m (Either Failure a) Source #

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

tryFailureJust :: Shell m => (Failure -> Maybe b) -> Proc a -> m (Either b a) Source #

Like tryFailure except that it takes an exception predicate which selects which exceptions to catch. Any exception not matching the predicate (returning Nothing) is re-thrown.

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

Run a Proc with an action to take if an exception is thrown.

catchFailureJust :: Shell m => (Failure -> Maybe b) -> Proc a -> (b -> Proc a) -> m a Source #

Like catchFailureJust except that it takes an exception predicate which selects which exceptions to catch. Any exceptions not matching the predicate (returning Nothing) are re-thrown.

failWithStdErr :: Shell io => Proc a -> io a Source #

Capture the stderr of the proc, and attach it to any Failure exceptions that are thrown. The stderr is also forwarded to downstream processes, or the inherited stderr handle. Note that capturing stderr inherently requires that the stderr is accumulated in memory, so be careful about processes that dump a lot of information.

exitCode :: (Functor m, Shell m) => Proc a -> m Int Source #

Run a Proc action returning the exit code of the process instead of throwing an exception.

>>> exitCode false
1

translateCode :: Shell m => (Int -> Maybe a) -> Proc a -> m a Source #

Apply a function to non-0 exit codes to extract a result. If Nothing is produced, the Failure is thrown.

translateCode' :: Shell m => (Int -> Maybe b) -> Proc a -> m (Either b a) Source #

Apply a function that translates non-0 exit codes to results. Any code that returns a Nothing will be thrown as a Failure.

Constructing Arguments

type Cmd = HasCallStack => forall a. Command a => a Source #

This type represents a partially built command. Further arguments can be supplied to it, or it can be turned into a Proc or directly executed in a context which supports that (such as IO).

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 and then encode it using the file system encoding.

Minimal complete definition

Nothing

Methods

asArg :: a -> [ByteString] Source #

default asArg :: Show a => a -> [ByteString] Source #

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

default asArgFromList :: Show a => [a] -> [ByteString] Source #

Instances

Instances details
ExecArg ByteString Source # 
Instance details

Defined in Shh.Internal

ExecArg ByteString Source # 
Instance details

Defined in Shh.Internal

ExecArg Integer Source # 
Instance details

Defined in Shh.Internal

ExecArg Char Source #

The Char and String instances encode using the file system encoding.

Instance details

Defined in Shh.Internal

ExecArg Int Source # 
Instance details

Defined in Shh.Internal

ExecArg Word Source # 
Instance details

Defined in Shh.Internal

ExecArg a => ExecArg [a] Source #

The [Char]/String instance encodes using the file system encoding.

Instance details

Defined in Shh.Internal

Methods

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

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

class Command a Source #

A class for building up a command.

Minimal complete definition

toArgs

Instances

Instances details
a ~ () => Command (IO a) Source #

Commands can be executed directly in IO

Instance details

Defined in Shh.Internal

Methods

toArgs :: [ByteString] -> IO a Source #

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

Defined in Shh.Internal

Methods

toArgs :: [ByteString] -> Proc a Source #

Command [ByteString] Source # 
Instance details

Defined in Shh.Internal

Command [ByteString] Source # 
Instance details

Defined in Shh.Internal

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

Defined in Shh.Internal

Methods

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

displayCommand :: Cmd -> [ByteString] Source #

This function turns a Cmd into a list of ByteStrings.

>>> displayCommand $ echo "Hello, world!"
["echo","Hello, world!"]

Template Haskell helpers

encodeIdentifier :: String -> String Source #

Takes a string, and makes a Haskell identifier out of it. If the string is a path, the filename portion is used. The exact transformation is that alphanumeric characters are unchanged, - becomes _, and ' is used to escape all other characters. _ becomes '_, . becomes '' and anthing else is becomes a hex encoded number surrounded by ' characters.

Justification for changing - to _ is that - appears far more commonly in executable names than _ does, and so we give it the more ergonomic encoding.

>>> encodeIdentifier "nix-shell"
"nix_shell"
>>> encodeIdentifier "R"
"_R"
>>> encodeIdentifier "x86_64-unknown-linux-gnu-gcc"
"x86'_64_unknown_linux_gnu_gcc"
>>> encodeIdentifier "release.sh"
"release''sh"

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 -> [FilePath] -> 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) -> [FilePath] -> 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". Be careful using this function in a program, as it doesn't play well with multiple threads. Best to just use it in an interactive shell or for very simple transliterations of shell scripts.

Utilities

class ToFilePath a where Source #

Things that can be converted to a FilePath.

The results must use the file system encoding. Use this if you want to pass a ByteString to openFile, or if you want to turn a FilePath into a ByteString.

If you never change the file system encoding, it should be safe to use unsafePerformIO on these functions.