shh-0.2.0.3: Simple shell scripting from Haskell

Safe HaskellNone
LanguageHaskell2010

Shh.Internal

Description

See documentation for Shh.

Synopsis

Documentation

initInteractive :: IO () Source #

This function needs to be called in order to use the library succesfully from GHCi.

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

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

Minimal complete definition

(|>), (|!>), (&>), (&!>), writeProc, withRead

Methods

(|>) :: Proc a -> Proc a -> f a 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.

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

(<|) :: Proc a -> Proc a -> f a Source #

Flipped version of |>

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

This is probably not what you want, see the &> and &!> operators for redirection.

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

Redirect stdout of this process to another location

ls &> Append "/dev/null"

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

Redirect stderr of this process to another location

ls &!> StdOut

writeProc :: Proc a -> String -> f a Source #

Provide the stdin of a Proc from a String

withRead :: 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, and the process is terminated.

Instances
PipeResult IO Source # 
Instance details

Defined in Shh.Internal

Methods

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

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

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

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

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

writeProc :: Proc a -> String -> IO a Source #

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

PipeResult Proc Source # 
Instance details

Defined in Shh.Internal

Methods

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

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

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

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

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

writeProc :: Proc a -> String -> Proc a Source #

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

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

Create a pipe, and close both ends on exception.

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"

newtype Proc a Source #

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

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 a -> Proc a -> Proc a Source #

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

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

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

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

writeProc :: Proc a -> String -> Proc a Source #

withRead :: NFData b => Proc a -> (String -> IO b) -> Proc b 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 #

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.

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

Create a Proc from a command and a list of arguments.

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.

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

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

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.

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 shasum "Hello"
"f7ff9e8b7bb2e09b70935a5d785e0cc5d9d0abf0  -\n"

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

Flipped, infix version of writeProc

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

Infix version of writeProc

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

What on a given ProcessHandle, and throw an exception of type Failure if it's exit code is non-zero (ignoring SIGPIPE)

trim :: String -> String 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 String 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 -> [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 where Source #

A class for building up a command

Methods

toArgs :: [String] -> a Source #

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

pathBins :: IO [FilePath] Source #

Get all files in a directory on your `$PATH`.

TODO: Check for executability.

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.

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

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

$(loadExeAs fnName executable) defines a function called fnName which executes the path in executable.

validIdentifier :: String -> Bool Source #

Checks if a String is a valid Haskell identifier.

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 ignored. It also creates the IO action missingExecutables which will do a runtime check to ensure all the executables that were found at compile time still exist.

checkExecutable :: FilePath -> IO Bool Source #

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

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.

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.

split0 :: String -> [String] Source #

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

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

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

readSplit0 $ find "-print0"

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

A convinience 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.