| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Shh
Description
Shh provides a shell-like environment for Haskell.
Synopsis
- initInteractive :: IO ()
- class Shell f where- runProc :: HasCallStack => Proc a -> f a
 
- exe :: (Command a, ExecArg str, HasCallStack) => str -> a
- mkProc :: HasCallStack => ByteString -> [ByteString] -> Proc ()
- mkProc' :: HasCallStack => Bool -> ByteString -> [ByteString] -> Proc ()
- data Proc a
- pureProc :: Shell io => (ByteString -> ByteString) -> io ()
- writeOutput :: (ExecArg a, Shell io) => a -> io ()
- writeError :: (ExecArg a, Shell io) => a -> io ()
- prefixLines :: Shell io => ByteString -> io ()
- readInput :: (NFData a, Shell io) => (ByteString -> IO a) -> io a
- readInputEndBy :: (NFData a, Shell io) => ByteString -> ([ByteString] -> IO a) -> io a
- readInputEndBy0 :: (NFData a, Shell io) => ([ByteString] -> IO a) -> io a
- readInputLines :: (NFData a, Shell io) => ([ByteString] -> IO a) -> io a
- readInputP :: (NFData a, Shell io) => (ByteString -> Proc a) -> io a
- readInputEndByP :: (NFData a, Shell io) => ByteString -> ([ByteString] -> Proc a) -> io a
- readInputEndBy0P :: (NFData a, Shell io) => ([ByteString] -> Proc a) -> io a
- readInputLinesP :: (NFData a, Shell io) => ([ByteString] -> Proc a) -> io a
- xargs1 :: (NFData a, Monoid a) => ByteString -> (ByteString -> Proc a) -> Proc a
- capture :: Shell io => io ByteString
- captureTrim :: Shell io => io ByteString
- captureEndBy :: Shell io => ByteString -> io [ByteString]
- captureEndBy0 :: Shell io => io [ByteString]
- captureLines :: Shell io => io [ByteString]
- (|>) :: Shell f => Proc a -> Proc b -> f b
- (|!>) :: Shell f => Proc a -> Proc b -> f b
- pipe :: Shell f => Proc a -> Proc b -> f (a, b)
- pipeErr :: Shell f => Proc a -> Proc b -> f (a, b)
- (&>) :: Shell f => Proc a -> Stream -> f a
- (&!>) :: Shell f => Proc a -> Stream -> f a
- (<|) :: Shell f => Proc a -> Proc b -> f a
- data Stream
- devNull :: Stream
- (<<<) :: Shell io => Proc a -> ByteString -> io a
- (>>>) :: Shell io => ByteString -> Proc a -> io a
- writeProc :: Shell io => Proc a -> ByteString -> io a
- apply :: (ExecArg a, Shell io) => Proc v -> a -> io ByteString
- trim :: ByteString -> ByteString
- endBy :: ByteString -> ByteString -> [ByteString]
- endBy0 :: ByteString -> [ByteString]
- data Failure = Failure {}
- ignoreFailure :: (Functor m, Shell m) => Proc a -> m ()
- ignoreCode :: (Monad m, Shell m) => Int -> Proc a -> m ()
- tryFailure :: Shell m => Proc a -> m (Either Failure a)
- tryFailureJust :: Shell m => (Failure -> Maybe b) -> Proc a -> m (Either b a)
- catchFailure :: Shell m => Proc a -> (Failure -> Proc a) -> m a
- catchFailureJust :: Shell m => (Failure -> Maybe b) -> Proc a -> (b -> Proc a) -> m a
- failWithStdErr :: Shell io => Proc a -> io a
- exitCode :: (Functor m, Shell m) => Proc a -> m Int
- translateCode :: Shell m => (Int -> Maybe a) -> Proc a -> m a
- translateCode' :: Shell m => (Int -> Maybe b) -> Proc a -> m (Either b a)
- type Cmd = HasCallStack => forall a. Command a => a
- class ExecArg a where- asArg :: a -> [ByteString]
- asArgFromList :: [a] -> [ByteString]
 
- class Command a
- displayCommand :: Cmd -> [ByteString]
- encodeIdentifier :: String -> String
- data ExecReference
- load :: ExecReference -> [FilePath] -> Q [Dec]
- loadEnv :: ExecReference -> Q [Dec]
- loadFromDirs :: [FilePath] -> Q [Dec]
- loadFromBins :: [FilePath] -> Q [Dec]
- loadAnnotated :: ExecReference -> (String -> String) -> [FilePath] -> Q [Dec]
- loadAnnotatedEnv :: ExecReference -> (String -> String) -> Q [Dec]
- loadAnnotatedFromDirs :: [FilePath] -> (String -> String) -> Q [Dec]
- loadExe :: ExecReference -> String -> Q [Dec]
- loadExeAs :: ExecReference -> String -> String -> Q [Dec]
- pathBins :: IO [FilePath]
- pathBinsAbs :: IO [FilePath]
- cd :: Cd a => a
- class ToFilePath a where- toFilePath :: a -> IO FilePath
- fromFilePath :: FilePath -> IO a
 
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
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 #
Constructing a Proc
You usually don't need to runProcProc
exe :: (Command a, ExecArg str, HasCallStack) => str -> a Source #
Execute the given command. Further arguments can be passed in.
exe "ls" "-l"
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.
mkProc' :: HasCallStack => Bool -> ByteString -> [ByteString] -> Proc () 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 # | |
| Functor Proc Source # | |
| Applicative Proc Source # | |
| MonadIO Proc Source # | |
| Defined in Shh.Internal | |
| Shell Proc Source # | |
| Defined in Shh.Internal | |
| Semigroup (Proc a) Source # | The  | 
| a ~ () => Monoid (Proc a) Source # | |
| a ~ () => Command (Proc a) Source # | |
| Defined in Shh.Internal Methods toArgs :: [ByteString] -> Proc a Source # | |
Native Processes (Lazy)
You can also create native Haskell Proc
NB: The functions here that operate on lazy ByteStringstdin, 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 Procstdin 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 Procstdout. 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 Procstderr.
 See also writeOutput
>>>writeError "Hello" &> devNullHello
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: " &> StdErrstdout: this is stdout stderr: this is stderr
readInputEndBy :: (NFData a, Shell io) => ByteString -> ([ByteString] -> IO a) -> io a Source #
readInputEndBy0 :: (NFData a, Shell io) => ([ByteString] -> IO a) -> io a Source #
readInputLines :: (NFData a, Shell io) => ([ByteString] -> IO a) -> io a Source #
readInputP :: (NFData a, Shell io) => (ByteString -> Proc a) -> io a Source #
readInputEndByP :: (NFData a, Shell io) => ByteString -> ([ByteString] -> Proc a) -> io a Source #
Like readInputP
readInputEndBy0P :: (NFData a, Shell io) => ([ByteString] -> Proc a) -> io a Source #
Like readInputP
readInputLinesP :: (NFData a, Shell io) => ([ByteString] -> Proc a) -> io a Source #
Like readInputP
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" |> cata b>>>printf "a\\0b" |> xargs1 "\0" echo |> cata 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 pureByteString into memory.
captureTrim :: Shell io => io ByteString Source #
captureEndBy :: Shell io => ByteString -> io [ByteString] Source #
captureEndBy0 :: Shell io => io [ByteString] Source #
Same as captureEndBy "\0"
captureLines :: Shell io => io [ByteString] Source #
Same as captureSplit "\n"
Piping and Redirection
(|>) :: Shell f => Proc a -> Proc b -> f b infixl 1 Source #
Use this to send the output of on 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" |> wc1 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
(&>) :: 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" &!> StdOutShh
(<|) :: Shell f => Proc a -> Proc b -> f a infixr 1 Source #
Flipped version of |> with lower precedence.
>>>captureTrim <| (echo "Hello" |> wc "-c")"6"
Type used to represent destinations for redirects. Truncate file> file in a shell, and Append file>> file.
Constructors
| StdOut | |
| StdErr | |
| Truncate ByteString | |
| Append ByteString | 
Writing to stdin
NB: See also writeOutput for an echo-like option. These are all
 implemented in terms of writeOutput.
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!).
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
| Show Failure Source # | |
| Exception Failure Source # | |
| Defined in Shh.Internal Methods toException :: Failure -> SomeException # fromException :: SomeException -> Maybe Failure # displayException :: Failure -> String # | |
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
tryFailureJust :: Shell m => (Failure -> Maybe b) -> Proc a -> m (Either b a) Source #
Like tryFailureNothing) 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 catchFailureJustNothing) are re-thrown.
failWithStdErr :: Shell io => Proc a -> io a Source #
Capture the stderr of the proc, and attach it to any Failure
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 false1
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
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 #
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
| ExecArg Char Source # | The  | 
| Defined in Shh.Internal | |
| ExecArg Int Source # | |
| Defined in Shh.Internal | |
| ExecArg Integer Source # | |
| Defined in Shh.Internal | |
| ExecArg Word Source # | |
| Defined in Shh.Internal | |
| ExecArg ByteString Source # | |
| Defined in Shh.Internal Methods asArg :: ByteString -> [ByteString] Source # asArgFromList :: [ByteString] -> [ByteString] Source # | |
| ExecArg ByteString Source # | |
| Defined in Shh.Internal Methods asArg :: ByteString -> [ByteString0] Source # asArgFromList :: [ByteString] -> [ByteString0] Source # | |
| ExecArg a => ExecArg [a] Source # | The  | 
| Defined in Shh.Internal | |
A class for building up a command.
Minimal complete definition
Instances
| Command [ByteString] Source # | |
| Defined in Shh.Internal Methods toArgs :: [ByteString] -> [ByteString] Source # | |
| Command [ByteString] Source # | |
| Defined in Shh.Internal Methods toArgs :: [ByteString0] -> [ByteString] Source # | |
| a ~ () => Command (IO a) Source # | Commands can be executed directly in IO | 
| Defined in Shh.Internal Methods toArgs :: [ByteString] -> IO a Source # | |
| a ~ () => Command (Proc a) Source # | |
| Defined in Shh.Internal Methods toArgs :: [ByteString] -> Proc a Source # | |
| (ExecArg b, Command a) => Command (b -> a) Source # | |
| Defined in Shh.Internal Methods toArgs :: [ByteString] -> b -> a Source # | |
displayCommand :: Cmd -> [ByteString] Source #
This function turns a Cmd into a list of ByteString
>>>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
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
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.
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.
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
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 openFileFilePath into a ByteString.
If you never change the file system encoding, it should be safe to use
 unsafePerformIO
Instances
| ToFilePath FilePath Source # | |
| Defined in Shh.Internal | |
| ToFilePath ByteString Source # | |
| Defined in Shh.Internal Methods toFilePath :: ByteString -> IO FilePath Source # fromFilePath :: FilePath -> IO ByteString Source # | |
| ToFilePath ByteString Source # | |
| Defined in Shh.Internal Methods toFilePath :: ByteString -> IO FilePath Source # fromFilePath :: FilePath -> IO ByteString Source # | |