Safe Haskell | None |
---|---|
Language | Haskell2010 |
See documentation for Shh.
Synopsis
- initInteractive :: IO ()
- data Failure = Failure {
- failureProg :: String
- failureArgs :: [String]
- failureCode :: Int
- class PipeResult f where
- withPipe :: (Handle -> Handle -> IO a) -> IO a
- data Stream
- devNull :: Stream
- newtype Proc a = Proc (Handle -> Handle -> Handle -> IO () -> IO () -> IO a)
- runProc :: Proc a -> IO a
- mkProc :: String -> [String] -> Proc ()
- readProc :: PipeResult io => Proc a -> io String
- withRead' :: (NFData b, PipeResult io) => (String -> a) -> Proc x -> (a -> IO b) -> io b
- withReadSplit0 :: (NFData b, PipeResult io) => Proc a -> ([String] -> IO b) -> io b
- withReadLines :: (NFData b, PipeResult io) => Proc a -> ([String] -> IO b) -> io b
- withReadWords :: (NFData b, PipeResult io) => Proc a -> ([String] -> IO b) -> io b
- readWriteProc :: MonadIO io => Proc a -> String -> io String
- apply :: MonadIO io => Proc a -> String -> io String
- (>>>) :: PipeResult io => String -> Proc a -> io a
- (<<<) :: PipeResult io => Proc a -> String -> io a
- waitProc :: String -> [String] -> ProcessHandle -> IO ()
- trim :: String -> String
- class ProcFailure m where
- catchFailure :: Proc a -> m (Either Failure a)
- ignoreFailure :: (Functor m, ProcFailure m) => Proc a -> m ()
- catchCode :: (Functor m, ProcFailure m) => Proc a -> m Int
- readTrim :: (Functor io, PipeResult io) => Proc a -> io String
- class ExecArg a where
- asArg :: a -> [String]
- asArgFromList :: [a] -> [String]
- class ExecArgs a where
- class Unit a
- pathBins :: IO [FilePath]
- exe :: (Unit a, ExecArgs a) => String -> a
- loadExe :: ExecReference -> String -> Q [Dec]
- data ExecReference
- loadExeAs :: ExecReference -> String -> String -> Q [Dec]
- validIdentifier :: String -> Bool
- loadEnv :: ExecReference -> Q [Dec]
- checkExecutable :: FilePath -> IO Bool
- load :: ExecReference -> [String] -> Q [Dec]
- loadAnnotated :: ExecReference -> (String -> String) -> [String] -> Q [Dec]
- loadAnnotatedEnv :: ExecReference -> (String -> String) -> Q [Dec]
- split0 :: String -> [String]
- readSplit0 :: Proc () -> IO [String]
- readLines :: Proc () -> IO [String]
- readWords :: Proc () -> IO [String]
- readAuto :: Read a => Proc () -> IO a
Documentation
initInteractive :: IO () Source #
This function needs to be called in order to use the library succesfully from GHCi.
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.
Failure | |
|
Instances
Eq Failure Source # | |
Ord Failure Source # | |
Show Failure Source # | |
Exception Failure Source # | |
Defined in Shh.Internal toException :: Failure -> SomeException # fromException :: SomeException -> Maybe Failure # displayException :: Failure -> String # |
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
).
(|>) :: 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 #
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 # | |
Defined in Shh.Internal (|>) :: 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 # | |
Defined in Shh.Internal (|>) :: 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.
Type representing a series or pipeline (or both) of shell commands.
Instances
Monad Proc Source # | |
Functor Proc Source # | |
Applicative Proc Source # | |
MonadIO Proc Source # | |
Defined in Shh.Internal | |
ProcFailure Proc Source # | |
Defined in Shh.Internal | |
PipeResult Proc Source # | |
Defined in Shh.Internal (|>) :: 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 |
a ~ () => Monoid (Proc a) Source # | |
ExecArgs (Proc ()) Source # | |
mkProc :: String -> [String] -> Proc () Source #
Create a Proc
from a command and a list of arguments.
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 #
withReadLines :: (NFData b, PipeResult io) => Proc a -> ([String] -> IO b) -> io b Source #
Like
except it splits the string with withRead
first.lines
NB: Please consider using
where you can.withReadSplit0
withReadWords :: (NFData b, PipeResult io) => Proc a -> ([String] -> IO b) -> io b Source #
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"
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)
class ProcFailure m where Source #
Instances
ProcFailure IO Source # | |
Defined in Shh.Internal | |
ProcFailure Proc Source # | |
Defined in Shh.Internal |
ignoreFailure :: (Functor m, ProcFailure m) => Proc a -> m () Source #
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
.
Nothing
asArg :: a -> [String] Source #
asArg :: Show a => a -> [String] Source #
asArgFromList :: [a] -> [String] Source #
asArgFromList :: Show a => [a] -> [String] Source #
class ExecArgs a where Source #
A class for building up a command
Force a `()` result.
Instances
a ~ () => Unit (m a) Source # | |
Defined in Shh.Internal | |
Unit b => Unit (a -> b) Source # | |
Defined in Shh.Internal |
pathBins :: IO [FilePath] Source #
Get all files in a directory on your `$PATH`.
TODO: Check for executability.
data ExecReference Source #
Specify how executables should be referenced.
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"