Safe Haskell | None |
---|---|
Language | Haskell98 |
- Entering Sh.
- Running external commands.
- Running commands Using handles
- Handle manipulation
- Modifying and querying environment.
- Environment directory
- Printing
- Querying filesystem.
- Filename helpers
- Manipulating filesystem.
- reading/writing Files
- exiting the program
- Exceptions
- convert between Text and FilePath
- Utility Functions
- Re-exported for your convenience
- internal functions for writing extensions
- find functions
A module for shell-like programming in Haskell. Shelly's focus is entirely on ease of use for those coming from shell scripting. However, it also tries to use modern libraries and techniques to keep things efficient.
The functionality provided by this module is (unlike standard Haskell filesystem functionality) thread-safe: each Sh maintains its own environment and its own working directory.
Recommended usage includes putting the following at the top of your program, otherwise you will likely need either type annotations or type conversions
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} import Shelly import qualified Data.Text as T default (T.Text)
Synopsis
- data Sh a
- type ShIO a = Sh a
- shelly :: MonadIO m => Sh a -> m a
- shellyNoDir :: MonadIO m => Sh a -> m a
- shellyFailDir :: MonadIO m => Sh a -> m a
- asyncSh :: Sh a -> Sh (Async a)
- sub :: Sh a -> Sh a
- silently :: Sh a -> Sh a
- verbosely :: Sh a -> Sh a
- escaping :: Bool -> Sh a -> Sh a
- print_stdout :: Bool -> Sh a -> Sh a
- print_stderr :: Bool -> Sh a -> Sh a
- print_commands :: Bool -> Sh a -> Sh a
- onCommandHandles :: StdInit -> Sh a -> Sh a
- tracing :: Bool -> Sh a -> Sh a
- errExit :: Bool -> Sh a -> Sh a
- log_stdout_with :: (Text -> IO ()) -> Sh a -> Sh a
- log_stderr_with :: (Text -> IO ()) -> Sh a -> Sh a
- run :: FilePath -> [Text] -> Sh Text
- run_ :: FilePath -> [Text] -> Sh ()
- runFoldLines :: a -> FoldCallback a -> FilePath -> [Text] -> Sh a
- cmd :: ShellCmd result => FilePath -> result
- type FoldCallback a = a -> Text -> a
- bash :: FilePath -> [Text] -> Sh Text
- bash_ :: FilePath -> [Text] -> Sh ()
- bashPipeFail :: (FilePath -> [Text] -> Sh a) -> FilePath -> [Text] -> Sh a
- (-|-) :: Sh Text -> Sh b -> Sh b
- lastStderr :: Sh Text
- setStdin :: Text -> Sh ()
- lastExitCode :: Sh Int
- command :: FilePath -> [Text] -> [Text] -> Sh Text
- command_ :: FilePath -> [Text] -> [Text] -> Sh ()
- command1 :: FilePath -> [Text] -> Text -> [Text] -> Sh Text
- command1_ :: FilePath -> [Text] -> Text -> [Text] -> Sh ()
- sshPairs :: Text -> [(FilePath, [Text])] -> Sh Text
- sshPairsPar :: Text -> [(FilePath, [Text])] -> Sh Text
- sshPairs_ :: Text -> [(FilePath, [Text])] -> Sh ()
- sshPairsPar_ :: Text -> [(FilePath, [Text])] -> Sh ()
- sshPairsWithOptions :: Text -> [Text] -> [(FilePath, [Text])] -> Sh Text
- sshCommandText :: [(FilePath, [Text])] -> SshMode -> Text
- data SshMode
- class ShellCmd t where
- class CmdArg a where
- runHandle :: FilePath -> [Text] -> (Handle -> Sh a) -> Sh a
- runHandles :: FilePath -> [Text] -> [StdHandle] -> (Handle -> Handle -> Handle -> Sh a) -> Sh a
- transferLinesAndCombine :: Handle -> (Text -> IO ()) -> IO Text
- transferFoldHandleLines :: a -> FoldCallback a -> Handle -> (Text -> IO ()) -> IO a
- data StdHandle
- data StdStream
- type HandleInitializer = Handle -> IO ()
- data StdInit = StdInit {}
- initOutputHandles :: HandleInitializer -> StdInit
- initAllHandles :: HandleInitializer -> StdInit
- setenv :: Text -> Text -> Sh ()
- get_env :: Text -> Sh (Maybe Text)
- get_env_text :: Text -> Sh Text
- getenv :: Text -> Sh Text
- get_env_def :: Text -> Text -> Sh Text
- get_env_all :: Sh [(String, String)]
- get_environment :: Sh [(String, String)]
- appendToPath :: FilePath -> Sh ()
- prependToPath :: FilePath -> Sh ()
- cd :: FilePath -> Sh ()
- chdir :: FilePath -> Sh a -> Sh a
- chdir_p :: FilePath -> Sh a -> Sh a
- pwd :: Sh FilePath
- echo :: Text -> Sh ()
- echo_n :: Text -> Sh ()
- echo_err :: Text -> Sh ()
- echo_n_err :: Text -> Sh ()
- inspect :: Show s => s -> Sh ()
- inspect_err :: Show s => s -> Sh ()
- tag :: Sh a -> Text -> Sh a
- trace :: Text -> Sh ()
- show_command :: FilePath -> [Text] -> Text
- ls :: FilePath -> Sh [FilePath]
- lsT :: FilePath -> Sh [Text]
- test_e :: FilePath -> Sh Bool
- test_f :: FilePath -> Sh Bool
- test_d :: FilePath -> Sh Bool
- test_s :: FilePath -> Sh Bool
- test_px :: FilePath -> Sh Bool
- which :: FilePath -> Sh (Maybe FilePath)
- absPath :: FilePath -> Sh FilePath
- (</>) :: (ToFilePath filepath1, ToFilePath filepath2) => filepath1 -> filepath2 -> FilePath
- (<.>) :: ToFilePath filepath => filepath -> Text -> FilePath
- canonic :: FilePath -> Sh FilePath
- canonicalize :: FilePath -> Sh FilePath
- relPath :: FilePath -> Sh FilePath
- relativeTo :: FilePath -> FilePath -> Sh FilePath
- path :: FilePath -> Sh FilePath
- hasExt :: Text -> FilePath -> Bool
- mv :: FilePath -> FilePath -> Sh ()
- rm :: FilePath -> Sh ()
- rm_f :: FilePath -> Sh ()
- rm_rf :: FilePath -> Sh ()
- cp :: FilePath -> FilePath -> Sh ()
- cp_r :: FilePath -> FilePath -> Sh ()
- mkdir :: FilePath -> Sh ()
- mkdir_p :: FilePath -> Sh ()
- mkdirTree :: Tree FilePath -> Sh ()
- readfile :: FilePath -> Sh Text
- readBinary :: FilePath -> Sh ByteString
- writefile :: FilePath -> Text -> Sh ()
- writeBinary :: FilePath -> ByteString -> Sh ()
- appendfile :: FilePath -> Text -> Sh ()
- touchfile :: FilePath -> Sh ()
- withTmpDir :: (FilePath -> Sh a) -> Sh a
- exit :: Int -> Sh a
- errorExit :: Text -> Sh a
- quietExit :: Int -> Sh a
- terror :: Text -> Sh a
- bracket_sh :: Sh a -> (a -> Sh b) -> (a -> Sh c) -> Sh c
- catchany :: IO a -> (SomeException -> IO a) -> IO a
- catch_sh :: Exception e => Sh a -> (e -> Sh a) -> Sh a
- handle_sh :: Exception e => (e -> Sh a) -> Sh a -> Sh a
- handleany_sh :: (SomeException -> Sh a) -> Sh a -> Sh a
- finally_sh :: Sh a -> Sh b -> Sh a
- data ShellyHandler a = Exception e => ShellyHandler (e -> Sh a)
- catches_sh :: Sh a -> [ShellyHandler a] -> Sh a
- catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh a
- data ReThrownException e = ReThrownException e String
- data RunFailed = RunFailed FilePath [Text] Int Text
- toTextIgnore :: FilePath -> Text
- toTextWarn :: FilePath -> Sh Text
- fromText :: Text -> FilePath
- whenM :: Monad m => m Bool -> m () -> m ()
- unlessM :: Monad m => m Bool -> m () -> m ()
- time :: Sh a -> Sh (Double, a)
- sleep :: Int -> Sh ()
- liftIO :: MonadIO m => IO a -> m a
- when :: Applicative f => Bool -> f () -> f ()
- unless :: Applicative f => Bool -> f () -> f ()
- type FilePath = String
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- get :: Sh State
- put :: State -> Sh ()
- find :: FilePath -> Sh [FilePath]
- findWhen :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
- findFold :: (a -> FilePath -> Sh a) -> a -> FilePath -> Sh a
- findDirFilter :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
- findDirFilterWhen :: (FilePath -> Sh Bool) -> (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath]
- findFoldDirFilter :: (a -> FilePath -> Sh a) -> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
- followSymlink :: Bool -> Sh a -> Sh a
Entering Sh.
Instances
Monad Sh Source # | |
Functor Sh Source # | |
MonadFail Sh Source # | |
Defined in Shelly.Base | |
Applicative Sh Source # | |
MonadIO Sh Source # | |
Defined in Shelly.Base | |
MonadThrow Sh Source # | |
Defined in Shelly.Base | |
MonadCatch Sh Source # | |
MonadMask Sh Source # | |
MonadShControl Sh Source # | |
MonadSh Sh Source # | |
MonadBase IO Sh Source # | |
Defined in Shelly.Base | |
MonadBaseControl IO Sh Source # | |
ShellCmd (Sh ()) Source # | |
(s ~ Text, Show s) => ShellCmd (Sh s) Source # | |
ShellCmd (Sh Text) Source # | |
newtype ShM Sh a Source # | |
Defined in Shelly.Lifted | |
type StM Sh a Source # | |
Defined in Shelly.Base |
Deprecated: Use Sh instead of ShIO
ShIO is Deprecated in favor of Sh
, which is easier to type.
shelly :: MonadIO m => Sh a -> m a Source #
Enter a Sh from (Monad)IO. The environment and working directories are inherited from the current process-wide values. Any subsequent changes in processwide working directory or environment are not reflected in the running Sh.
shellyNoDir :: MonadIO m => Sh a -> m a Source #
Deprecated: Just use shelly. The default settings have changed
Deprecated now, just use shelly
, whose default has been changed.
Using this entry point does not create a .shelly
directory in the case
of failure. Instead it logs directly into the standard error stream (stderr
).
shellyFailDir :: MonadIO m => Sh a -> m a Source #
Using this entry point creates a .shelly
directory in the case
of failure where errors are recorded.
asyncSh :: Sh a -> Sh (Async a) Source #
spawn an asynchronous action with a copy of the current state
Enter a sub-Sh that inherits the environment The original state will be restored when the sub-Sh completes. Exceptions are propagated normally.
silently :: Sh a -> Sh a Source #
Create a sub-Sh in which external command outputs are not echoed and
commands are not printed.
See sub
.
verbosely :: Sh a -> Sh a Source #
Create a sub-Sh in which external command outputs are echoed and
Executed commands are printed
See sub
.
escaping :: Bool -> Sh a -> Sh a Source #
Create a sub-Sh with shell character escaping on or off.
Defaults to True
.
Setting to False
allows for shell wildcard such as * to be expanded by the shell along with any other special shell characters.
As a side-effect, setting to False
causes changes to PATH
to be ignored:
see the run
documentation.
print_stdout :: Bool -> Sh a -> Sh a Source #
Create a sub-Sh with stdout printing on or off Defaults to True.
print_stderr :: Bool -> Sh a -> Sh a Source #
Create a sub-Sh with stderr printing on or off Defaults to True.
print_commands :: Bool -> Sh a -> Sh a Source #
Create a sub-Sh with command echoing on or off
Defaults to False, set to True by verbosely
onCommandHandles :: StdInit -> Sh a -> Sh a Source #
When running an external command, apply the given initializers to the specified handles for that command. This can for example be used to change the encoding of the handles or set them into binary mode.
tracing :: Bool -> Sh a -> Sh a Source #
Create a sub-Sh where commands are not traced Defaults to True. You should only set to False temporarily for very specific reasons
errExit :: Bool -> Sh a -> Sh a Source #
named after bash -e errexit. Defaults to True
.
When True
, throw an exception on a non-zero exit code.
When False
, ignore a non-zero exit code.
Not recommended to set to False
unless you are specifically checking the error code with lastExitCode
.
log_stderr_with :: (Text -> IO ()) -> Sh a -> Sh a Source #
Create a sub-Sh in which stderr is sent to the user-defined
logger. When running with silently
the given log will not be
called for any output. However, unlike log_stdout_with
the log
will be called for output from run_
and bash_
commands.
Running external commands.
run :: FilePath -> [Text] -> Sh Text Source #
Execute an external command. Takes the command name and arguments.
You may prefer using cmd
instead, which is a variadic argument version
of this function.
stdout
and stderr
are collected. The stdout
is returned as
a result of run
, and complete stderr output is available after the fact using
lastStderr
All of the stdout output will be loaded into memory.
You can avoid this if you don't need stdout by using run_
,
If you want to avoid the memory and need to process the output then use runFoldLines
or runHandle
or runHandles
.
By default shell characters are escaped and
the command name is a name of a program that can be found via PATH
.
Shelly will look through the PATH
itself to find the command.
When escaping
is set to False
, shell characters are allowed.
Since there is no longer a guarantee that a single program name is
given, Shelly cannot look in the PATH
for it.
a PATH
modified by setenv is not taken into account when finding the exe name.
Instead the original Haskell program PATH
is used.
On a Posix system the env
command can be used to make the setenv
PATH used when escaping
is set to False. env echo hello
instead of echo hello
run_ :: FilePath -> [Text] -> Sh () Source #
the same as run
, but return ()
instead of the stdout content
stdout will be read and discarded line-by-line
runFoldLines :: a -> FoldCallback a -> FilePath -> [Text] -> Sh a Source #
used by run
. fold over stdout line-by-line as it is read to avoid keeping it in memory
stderr is still being placed in memory under the assumption it is always relatively small
cmd :: ShellCmd result => FilePath -> result Source #
variadic argument version of run
.
Please see the documenation for run
.
The syntax is more convenient, but more importantly it also allows the use of a FilePath as a command argument.
So an argument can be a Text or a FilePath without manual conversions.
a FilePath is automatically converted to Text with toTextIgnore
.
Convenient usage of cmd
requires the following:
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} import Shelly import qualified Data.Text as T default (T.Text)
type FoldCallback a = a -> Text -> a Source #
bash :: FilePath -> [Text] -> Sh Text Source #
Like run
, but it invokes the user-requested program with _bash_.
bashPipeFail :: (FilePath -> [Text] -> Sh a) -> FilePath -> [Text] -> Sh a Source #
Use this with bash
to set _pipefail_
bashPipeFail $ bash "echo foo | echo"
(-|-) :: Sh Text -> Sh b -> Sh b Source #
Pipe operator. set the stdout the first command as the stdin of the second.
This does not create a shell-level pipe, but hopefully it will in the future.
To create a shell level pipe you can set escaping False
and use a pipe |
character in a command.
lastExitCode :: Sh Int Source #
The exit code from the last command.
Unless you set errExit
to False you won't get a chance to use this: a non-zero exit code will throw an exception.
command :: FilePath -> [Text] -> [Text] -> Sh Text Source #
bind some arguments to run
for re-use. Example:
monit = command "monit" ["-c", "monitrc"] monit ["stop", "program"]
command_ :: FilePath -> [Text] -> [Text] -> Sh () Source #
bind some arguments to run_
for re-use. Example:
monit_ = command_ "monit" ["-c", "monitrc"] monit_ ["stop", "program"]
command1 :: FilePath -> [Text] -> Text -> [Text] -> Sh Text Source #
bind some arguments to run
for re-use, and require 1 argument. Example:
git = command1 "git" [] git "pull" ["origin", "master"]
command1_ :: FilePath -> [Text] -> Text -> [Text] -> Sh () Source #
bind some arguments to run_
for re-use, and require 1 argument. Example:
git_ = command1_ "git" [] git "pull" ["origin", "master"]
sshPairs :: Text -> [(FilePath, [Text])] -> Sh Text Source #
run commands over SSH.
An ssh executable is expected in your path.
Commands are in the same form as run
, but given as pairs
sshPairs "server-name" [("cd", "dir"), ("rm",["-r","dir2"])]
This interface is crude, but it works for now.
Please note this sets escaping
to False, and the remote commands are
quoted with single quotes, in a way such that the remote commands will see
the literal values you passed, this means that no variable expansion and
alike will done on either the local shell or the remote shell, and that
if there are a single or double quotes in your arguments, they need not
to be quoted manually.
Internally the list of commands are combined with the string &&
before given to ssh.
sshPairsPar :: Text -> [(FilePath, [Text])] -> Sh Text Source #
Same as sshPairs, but combines commands with the string &
, so they will be started in parallell.
:: Text | Server name. |
-> [Text] | Arguments to ssh (e.g. ["-p","22"]). |
-> [(FilePath, [Text])] | Pairs of commands to run on the remote. |
-> Sh Text | Returns the standard output. |
Like sshPairs
, but allows for arguments to the call to ssh.
class ShellCmd t where Source #
For the variadic function cmd
partially applied variadic functions require type signatures
Instances
MonadSh m => ShellCmd (m ()) Source # | |
(MonadSh m, s ~ Text, Show s) => ShellCmd (m s) Source # | |
MonadSh m => ShellCmd (m Text) Source # | |
ShellCmd (Sh ()) Source # | |
(s ~ Text, Show s) => ShellCmd (Sh s) Source # | |
ShellCmd (Sh Text) Source # | |
(CmdArg arg, ShellCmd result) => ShellCmd ([arg] -> result) Source # | |
(CmdArg arg, ShellCmd result) => ShellCmd (arg -> result) Source # | |
Running commands Using handles
Similar to run
but gives the raw stdout handle in a callback.
If you want even more control, use runHandles
.
:: FilePath | command |
-> [Text] | arguments |
-> [StdHandle] | optionally connect process i/o handles to existing handles |
-> (Handle -> Handle -> Handle -> Sh a) | stdin, stdout and stderr |
-> Sh a |
Similar to run
but gives direct access to all input and output handles.
Be careful when using the optional input handles. If you specify Inherit for a handle then attempting to access the handle in your callback is an error
transferLinesAndCombine :: Handle -> (Text -> IO ()) -> IO Text Source #
Transfer from one handle to another For example, send contents of a process output to stdout. does not close the write handle.
Also, return the complete contents being streamed line by line.
transferFoldHandleLines :: a -> FoldCallback a -> Handle -> (Text -> IO ()) -> IO a Source #
Transfer from one handle to another For example, send contents of a process output to stdout. does not close the write handle.
Also, fold over the contents being streamed line by line
Inherit | Inherit Handle from parent |
UseHandle Handle | Use the supplied Handle |
CreatePipe | Create a new pipe. The returned
|
NoStream | No stream handle will be passed |
Handle manipulation
type HandleInitializer = Handle -> IO () Source #
Initialize a handle before using it
A collection of initializers for the three standard process handles
initOutputHandles :: HandleInitializer -> StdInit Source #
Apply a single initializer to the two output process handles (stdout and stderr)
initAllHandles :: HandleInitializer -> StdInit Source #
Apply a single initializer to all three standard process handles (stdin, stdout and stderr)
Modifying and querying environment.
setenv :: Text -> Text -> Sh () Source #
Set an environment variable. The environment is maintained in Sh internally, and is passed to any external commands to be executed.
get_env :: Text -> Sh (Maybe Text) Source #
Fetch the current value of an environment variable. if non-existant or empty text, will be Nothing
get_env_text :: Text -> Sh Text Source #
Fetch the current value of an environment variable. Both empty and non-existent variables give empty string as a result.
get_env_def :: Text -> Text -> Sh Text Source #
Deprecated: use fromMaybe DEFAULT get_env
Fetch the current value of an environment variable. Both empty and non-existent variables give the default Text value as a result
appendToPath :: FilePath -> Sh () Source #
add the filepath onto the PATH env variable
prependToPath :: FilePath -> Sh () Source #
prepend the filepath to the PATH env variable
similar to appendToPath
but gives high priority to the filepath instead of low priority.
Environment directory
cd :: FilePath -> Sh () Source #
Change current working directory of Sh. This does *not* change the working directory of the process we are running it. Instead, Sh keeps track of its own working directory and builds absolute paths internally instead of passing down relative paths.
chdir :: FilePath -> Sh a -> Sh a Source #
cd
, execute a Sh action in the new directory and then pop back to the original directory
chdir_p :: FilePath -> Sh a -> Sh a Source #
chdir
, but first create the directory if it does not exit
Printing
echo :: Text -> Sh () Source #
Echo text to standard (error, when using _err variants) output. The _n variants do not print a final newline.
echo_n :: Text -> Sh () Source #
Echo text to standard (error, when using _err variants) output. The _n variants do not print a final newline.
echo_err :: Text -> Sh () Source #
Echo text to standard (error, when using _err variants) output. The _n variants do not print a final newline.
echo_n_err :: Text -> Sh () Source #
Echo text to standard (error, when using _err variants) output. The _n variants do not print a final newline.
Querying filesystem.
ls :: FilePath -> Sh [FilePath] Source #
List directory contents. Does *not* include "." and "..", but it does include (other) hidden files.
which :: FilePath -> Sh (Maybe FilePath) Source #
Get a full path to an executable by looking at the PATH
environement
variable. Windows normally looks in additional places besides the
PATH
: this does not duplicate that behavior.
Filename helpers
absPath :: FilePath -> Sh FilePath Source #
Make a relative path absolute by combining with the working directory.
An absolute path is returned as is.
To create a relative path, use relPath
.
(</>) :: (ToFilePath filepath1, ToFilePath filepath2) => filepath1 -> filepath2 -> FilePath Source #
uses System.FilePath, but can automatically convert a Text
(<.>) :: ToFilePath filepath => filepath -> Text -> FilePath Source #
uses System.FilePath, but can automatically convert a Text
canonic :: FilePath -> Sh FilePath Source #
makes an absolute path.
Like canonicalize
, but on an exception returns absPath
canonicalize :: FilePath -> Sh FilePath Source #
Obtain a (reasonably) canonic file path to a filesystem object. Based on "canonicalizePath" in system-fileio.
relPath :: FilePath -> Sh FilePath Source #
Makes a relative path relative to the current Sh working directory.
An absolute path is returned as is.
To create an absolute path, use absPath
make the second path relative to the first
Uses stripPrefix
, but will canonicalize the paths if necessary
path :: FilePath -> Sh FilePath Source #
Deprecated: use absPath, canonic, or relPath instead
deprecated
Manipulating filesystem.
mv :: FilePath -> FilePath -> Sh () Source #
Move a file. The second path could be a directory, in which case the
original file is moved into that directory.
wraps directory renameFile
, which may not work across FS boundaries
rm :: FilePath -> Sh () Source #
Remove a file.
Does fail if the file does not exist (use rm_f
instead) or is not a file.
rm_f :: FilePath -> Sh () Source #
Remove a file. Does not fail if the file does not exist. Does fail if the file is not a file.
rm_rf :: FilePath -> Sh () Source #
A swiss army cannon for removing things. Actually this goes farther than a
normal rm -rf, as it will circumvent permission problems for the files we
own. Use carefully.
Uses removeDirectoryRecursive
cp :: FilePath -> FilePath -> Sh () Source #
Copy a file. The second path could be a directory, in which case the original file name is used, in that directory.
mkdir_p :: FilePath -> Sh () Source #
Create a new directory, including parents (succeeds if the directory already exists).
mkdirTree :: Tree FilePath -> Sh () Source #
Create a new directory tree. You can describe a bunch of directories as a tree and this function will create all subdirectories. An example:
exec = mkTree $ "package" # [ "src" # [ "Data" # leaves ["Tree", "List", "Set", "Map"] ], "test" # leaves ["QuickCheck", "HUnit"], "dist/doc/html" # [] ] where (#) = Node leaves = map (# [])
reading/writing Files
readBinary :: FilePath -> Sh ByteString Source #
wraps ByteSting readFile
writeBinary :: FilePath -> ByteString -> Sh () Source #
withTmpDir :: (FilePath -> Sh a) -> Sh a Source #
Create a temporary directory and pass it as a parameter to a Sh computation. The directory is nuked afterwards.
exiting the program
Exceptions
catchany :: IO a -> (SomeException -> IO a) -> IO a Source #
A helper to catch any exception (same as
...
).catch
(e :: SomeException) -> ...
catch_sh :: Exception e => Sh a -> (e -> Sh a) -> Sh a Source #
Same as a normal catch
but specialized for the Sh monad.
handle_sh :: Exception e => (e -> Sh a) -> Sh a -> Sh a Source #
Same as a normal handle
but specialized for the Sh monad.
handleany_sh :: (SomeException -> Sh a) -> Sh a -> Sh a Source #
Handle any exception in the Sh monad.
data ShellyHandler a Source #
You need to wrap exception handlers with this when using catches_sh
.
Exception e => ShellyHandler (e -> Sh a) |
catches_sh :: Sh a -> [ShellyHandler a] -> Sh a Source #
catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh a Source #
Catch any exception in the Sh monad.
data ReThrownException e Source #
Shelly's wrapper around exceptions thrown in its monad
Instances
Exception e => Show (ReThrownException e) Source # | |
Defined in Shelly showsPrec :: Int -> ReThrownException e -> ShowS # show :: ReThrownException e -> String # showList :: [ReThrownException e] -> ShowS # | |
Exception e => Exception (ReThrownException e) Source # | |
Defined in Shelly toException :: ReThrownException e -> SomeException # fromException :: SomeException -> Maybe (ReThrownException e) # displayException :: ReThrownException e -> String # |
Instances
Show RunFailed Source # | |
Exception RunFailed Source # | |
Defined in Shelly toException :: RunFailed -> SomeException # fromException :: SomeException -> Maybe RunFailed # displayException :: RunFailed -> String # |
convert between Text and FilePath
toTextIgnore :: FilePath -> Text Source #
silently uses the Right or Left value of "Filesystem.Path.CurrentOS.toText"
Utility Functions
whenM :: Monad m => m Bool -> m () -> m () Source #
A monadic-conditional version of the "when" guard.
unlessM :: Monad m => m Bool -> m () -> m () Source #
A monadic-conditional version of the unless
guard.
time :: Sh a -> Sh (Double, a) Source #
Run a Sh computation and collect timing information.
The value returned is the amount of _real_ time spent running the computation
in seconds, as measured by the system clock.
The precision is determined by the resolution of getCurrentTime
.
Re-exported for your convenience
when :: Applicative f => Bool -> f () -> f () #
Conditional execution of Applicative
expressions. For example,
when debug (putStrLn "Debugging")
will output the string Debugging
if the Boolean value debug
is True
, and otherwise do nothing.
unless :: Applicative f => Bool -> f () -> f () #
The reverse of when
.
File and directory names are values of type String
, whose precise
meaning is operating system dependent. Files can be opened, yielding a
handle which can then be used to operate on the contents of that file.
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
internal functions for writing extensions
find functions
find :: FilePath -> Sh [FilePath] Source #
List directory recursively (like the POSIX utility "find"). listing is relative if the path given is relative. If you want to filter out some results or fold over them you can do that with the returned files. A more efficient approach is to use one of the other find functions.
findWhen :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath] Source #
find
that filters the found files as it finds.
Files must satisfy the given filter to be returned in the result.
findDirFilter :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath] Source #
find
that filters out directories as it finds
Filtering out directories can make a find much more efficient by avoiding entire trees of files.
:: (FilePath -> Sh Bool) | directory filter |
-> (FilePath -> Sh Bool) | file filter |
-> FilePath | directory |
-> Sh [FilePath] |
similar findWhen
, but also filter out directories
Alternatively, similar to findDirFilter
, but also filter out files
Filtering out directories makes the find much more efficient