shh-0.6.0.0: Simple shell scripting from Haskell

Safe HaskellNone
LanguageHaskell2010

Shh.Internal

Description

See documentation for Shh.

Synopsis

Documentation

For doc-tests. Not sure I can use TH in doc tests. >>> :seti -XOverloadedStrings >>> import Data.Monoid >>> let cat = exe "cat" >>> let echo = exe "echo" >>> let false = exe "false" >>> let head = exe "head" >>> let md5sum = exe "md5sum" >>> let printf = exe "printf" >>> let sleep = exe "sleep" >>> let true = exe "true" >>> let wc = exe "wc" >>> let xargs = exe "xargs" >>> let yes = exe "yes" >>> let some_command = writeOutput "this is stdout" >> (writeOutput "this is stderr" &> StdErr)

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.

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.

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

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

(|!>) :: 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"

withPipe :: (Handle -> Handle -> IO a) -> IO a Source #

Create a pipe, and close both ends on exception. The first argument is the read end, the second is the write end.

>>> withPipe $ \r w -> hPutStr w "test" >> hClose w >> hGetLine r
"test"

writeOutput :: (ExecArg a, PipeResult 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, PipeResult io) => a -> io () Source #

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

>>> writeError "Hello" &> devNull
Hello

readInput :: (NFData a, PipeResult 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"

unlines :: [ByteString] -> ByteString Source #

Join a list of ByteStrings with newline characters, terminating it with a newline.

readInputSplit :: (NFData a, PipeResult io) => ByteString -> ([ByteString] -> 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) => ([ByteString] -> 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) => ([ByteString] -> IO a) -> io a Source #

Like readInput, but splits the string on new lines.

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

pureProc :: PipeResult 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"

prefixLines :: PipeResult 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

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

Provide the stdin of a Proc from a ByteString

Same as writeOutput s |> p

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

Run a process and capture its 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

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

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

Constructors

Proc (Handle -> Handle -> Handle -> IO () -> IO () -> IO a) 
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 :: [ByteString] -> Proc () Source #

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.

runProc' :: Handle -> Handle -> Handle -> Proc a -> IO a Source #

Run's a Proc in IO. Like runProc, but you get to choose the handles. This is UNSAFE to expose externally, because there are restrictions on what the Handle can be. Within shh, we never call runProc' with invalid handles, so we ignore that corner case (see hDup).

mkProc' :: Bool -> ByteString -> [ByteString] -> 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.

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

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

readProc :: PipeResult io => Proc a -> io ByteString 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 ByteString. See withRead for a lazy version that can be used for streaming.

capture :: PipeResult 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"

captureTrim :: PipeResult io => io ByteString Source #

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

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

captureSplit :: PipeResult 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

withRead' :: (NFData b, PipeResult io) => (ByteString -> a) -> Proc x -> (a -> IO b) -> io b Source #

Apply a transformation function to the string before the IO action.

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

Like withRead except it splits the string with the provided separator.

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

Like withRead except it splits the string with split0 first.

withReadLines :: (NFData b, PipeResult io) => Proc a -> ([ByteString] -> 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 -> ([ByteString] -> IO b) -> io b Source #

Like withRead except it splits the string with words first.

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

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

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

Some as readWriteProc. Apply a Proc to a ByteString.

> apply md5sum "Hello"

"8b1a9953c4611296a827abf8c47804d7 -n"

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

Flipped, infix version of writeProc

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

Infix version of writeProc

waitProc :: ByteString -> [ByteString] -> ProcessHandle -> IO () Source #

Wait on a given ProcessHandle, and throw an exception of type Failure if its exit code is non-zero (ignoring SIGPIPE)

trim :: ByteString -> ByteString Source #

Trim leading and tailing whitespace.

class ProcFailure m where Source #

Allow us to catch Failure exceptions in IO and Proc

Methods

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

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

Instances
ProcFailure IO Source # 
Instance details

Defined in Shh.Internal

ProcFailure Proc 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

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.

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

Like readProc, but trim leading and tailing whitespace.

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 -> [ByteString] Source #

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

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

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

Instances
ExecArg Char Source #

The Char and String instances encodes as UTF8

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 ByteString Source # 
Instance details

Defined in Shh.Internal

ExecArg a => ExecArg [a] Source #

The [Char]/String instance encodes as UTF8

Instance details

Defined in Shh.Internal

Methods

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

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

class ExecArgs a where Source #

A class for building up a command

Methods

toArgs :: [ByteString] -> a Source #

Instances
ExecArgs (IO ()) Source #

Commands can be executed directly in IO

Instance details

Defined in Shh.Internal

Methods

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

ExecArgs (Proc ()) Source # 
Instance details

Defined in Shh.Internal

Methods

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

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

Defined in Shh.Internal

Methods

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

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.

findBinsIn :: [FilePath] -> IO [FilePath] Source #

Get all uniquely named executables from the list of directories. Returns a list of absolute file names.

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

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

exe "ls" "-l"

See also loadExe and loadEnv.

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

Create a function for the executable named

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

rawExe :: String -> String -> Q [Dec] Source #

Template Haskell function to create a function from a path that will be called. This does not check for executability at compile time.

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.

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"

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.

checkExecutable :: FilePath -> IO Bool Source #

Test to see if an executable can be found either on the $PATH or absolute.

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.

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.

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

Split a string separated by the provided separator. Trailing separators are ignored, and do not produce an empty string. Compatible with the output of most CLI programs, such as find -print0.

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

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.

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

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

split0 :: ByteString -> [ByteString] Source #

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

readSplit0 :: Proc () -> IO [ByteString] 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 [ByteString] Source #

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

Note: Please consider using readSplit0 instead if you can.

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

Read output into a list of words

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

Like readProc, but attempts to read the result.

cd' :: FilePath -> IO () Source #

Mimics the shell builtin "cd".

class Cd a where Source #

Helper class for variable number of arguments to cd builtin.

Methods

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

Instances
io ~ IO () => Cd io Source # 
Instance details

Defined in Shh.Internal

Methods

cd :: io Source #

(io ~ IO (), path ~ FilePath) => Cd (path -> io) Source # 
Instance details

Defined in Shh.Internal

Methods

cd :: path -> io Source #

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}

readInputP :: (NFData a, PipeResult 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.

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

Like readInputP, but splits the input.

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

Like readInputP, but splits the input on 0 bytes.

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

Like readInputP, but splits the input on new lines.

withNullInput :: (Handle -> IO a) -> IO a Source #

Create a null file handle.

withDuplicate :: Handle -> (Handle -> IO a) -> IO a Source #

Bracket a hDup

withDuplicates :: Handle -> Handle -> Handle -> (Handle -> Handle -> Handle -> IO a) -> IO a Source #

Bracket three hDups

withDuplicateNullInput :: Handle -> Handle -> (Handle -> Handle -> Handle -> IO a) -> IO a Source #

Bracket two hDups and provide a null input handle.

hDup :: Handle -> IO Handle Source #

Duplicate a Handle without trying to flush buffers. Only works on FileHandles.

hDuplicate tries to "flush" read buffers by seeking backwards, which doesn't work for streams/pipes. Since we are simulating a fork + exec in nativeProc, losing the buffers is actually the expected behaviour. (System.Process doesn't attempt to flush the buffers).

NB: An alternate solution that we could implement (even for System.Process forks) is to create a fresh pipe and spawn an async task to forward buffered content from the original handle if there is something in the buffer. My concern would be that it might be a performance hit that people aren't expecting.

Code basically copied from http://hackage.haskell.org/package/base-4.12.0.0/docs/src/GHC.IO.Handle.html#hDuplicate with minor modifications.

dupHandleShh :: FilePath -> Handle -> Maybe (MVar Handle__) -> Handle__ -> Maybe HandleFinalizer -> IO Handle Source #

Helper function for duplicating a Handle

dupHandleShh_ :: (IODevice dev, BufferedIO dev, Typeable dev) => dev -> FilePath -> Maybe (MVar Handle__) -> Handle__ -> Maybe HandleFinalizer -> IO Handle Source #

Helper function for duplicating a Handle