Safe Haskell | None |
---|---|
Language | Haskell98 |
- Entering Sh.
- Running external commands.
- Running commands Using handles
- 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)
- class Monad m => MonadSh m where
- 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
- sub :: MonadShControl m => m a -> m a
- silently :: MonadShControl m => m a -> m a
- verbosely :: MonadShControl m => m a -> m a
- escaping :: MonadShControl m => Bool -> m a -> m a
- print_stdout :: MonadShControl m => Bool -> m a -> m a
- print_stderr :: MonadShControl m => Bool -> m a -> m a
- print_commands :: MonadShControl m => Bool -> m a -> m a
- tracing :: MonadShControl m => Bool -> m a -> m a
- errExit :: MonadShControl m => Bool -> m a -> m a
- log_stdout_with :: MonadShControl m => (Text -> IO ()) -> m a -> m a
- log_stderr_with :: MonadShControl m => (Text -> IO ()) -> m a -> m a
- run :: MonadSh m => FilePath -> [Text] -> m Text
- run_ :: MonadSh m => FilePath -> [Text] -> m ()
- runFoldLines :: MonadSh m => a -> FoldCallback a -> FilePath -> [Text] -> m a
- cmd :: ShellCmd result => FilePath -> result
- type FoldCallback a = a -> Text -> a
- (-|-) :: (MonadShControl m, MonadSh m) => m Text -> m b -> m b
- lastStderr :: MonadSh m => m Text
- setStdin :: MonadSh m => Text -> m ()
- lastExitCode :: MonadSh m => m Int
- command :: MonadSh m => FilePath -> [Text] -> [Text] -> m Text
- command_ :: MonadSh m => FilePath -> [Text] -> [Text] -> m ()
- command1 :: MonadSh m => FilePath -> [Text] -> Text -> [Text] -> m Text
- command1_ :: MonadSh m => FilePath -> [Text] -> Text -> [Text] -> m ()
- sshPairs :: MonadSh m => Text -> [(FilePath, [Text])] -> m Text
- sshPairs_ :: MonadSh m => Text -> [(FilePath, [Text])] -> m ()
- class ShellCmd t where
- class CmdArg a where
- runHandle :: MonadShControl m => FilePath -> [Text] -> (Handle -> m a) -> m a
- runHandles :: MonadShControl m => FilePath -> [Text] -> [StdHandle] -> (Handle -> Handle -> Handle -> m a) -> m a
- transferLinesAndCombine :: MonadIO m => Handle -> (Text -> IO ()) -> m Text
- transferFoldHandleLines :: a -> FoldCallback a -> Handle -> (Text -> IO ()) -> IO a
- data StdHandle
- data StdStream :: *
- setenv :: MonadSh m => Text -> Text -> m ()
- get_env :: MonadSh m => Text -> m (Maybe Text)
- get_env_text :: MonadSh m => Text -> m Text
- get_env_all :: MonadSh m => m [(String, String)]
- appendToPath :: MonadSh m => FilePath -> m ()
- cd :: MonadSh m => FilePath -> m ()
- chdir :: MonadShControl m => FilePath -> m a -> m a
- chdir_p :: MonadShControl m => FilePath -> m a -> m a
- pwd :: MonadSh m => m FilePath
- echo :: MonadSh m => Text -> m ()
- echo_n :: MonadSh m => Text -> m ()
- echo_err :: MonadSh m => Text -> m ()
- echo_n_err :: MonadSh m => Text -> m ()
- inspect :: (Show s, MonadSh m) => s -> m ()
- inspect_err :: (Show s, MonadSh m) => s -> m ()
- tag :: (MonadShControl m, MonadSh m) => m a -> Text -> m a
- trace :: MonadSh m => Text -> m ()
- show_command :: FilePath -> [Text] -> Text
- ls :: MonadSh m => FilePath -> m [FilePath]
- lsT :: MonadSh m => FilePath -> m [Text]
- test_e :: MonadSh m => FilePath -> m Bool
- test_f :: MonadSh m => FilePath -> m Bool
- test_d :: MonadSh m => FilePath -> m Bool
- test_s :: MonadSh m => FilePath -> m Bool
- test_px :: MonadSh m => FilePath -> m Bool
- which :: MonadSh m => FilePath -> m (Maybe FilePath)
- absPath :: MonadSh m => FilePath -> m FilePath
- (</>) :: (ToFilePath filepath1, ToFilePath filepath2) => filepath1 -> filepath2 -> FilePath
- (<.>) :: ToFilePath filepath => filepath -> Text -> FilePath
- canonic :: MonadSh m => FilePath -> m FilePath
- canonicalize :: MonadSh m => FilePath -> m FilePath
- relPath :: MonadSh m => FilePath -> m FilePath
- relativeTo :: MonadSh m => FilePath -> FilePath -> m FilePath
- hasExt :: Text -> FilePath -> Bool
- mv :: MonadSh m => FilePath -> FilePath -> m ()
- rm :: MonadSh m => FilePath -> m ()
- rm_f :: MonadSh m => FilePath -> m ()
- rm_rf :: MonadSh m => FilePath -> m ()
- cp :: MonadSh m => FilePath -> FilePath -> m ()
- cp_r :: MonadSh m => FilePath -> FilePath -> m ()
- mkdir :: MonadSh m => FilePath -> m ()
- mkdir_p :: MonadSh m => FilePath -> m ()
- mkdirTree :: MonadSh m => Tree FilePath -> m ()
- readfile :: MonadSh m => FilePath -> m Text
- readBinary :: MonadSh m => FilePath -> m ByteString
- writefile :: MonadSh m => FilePath -> Text -> m ()
- appendfile :: MonadSh m => FilePath -> Text -> m ()
- touchfile :: MonadSh m => FilePath -> m ()
- withTmpDir :: MonadShControl m => (FilePath -> m a) -> m a
- exit :: MonadSh m => Int -> m a
- errorExit :: MonadSh m => Text -> m a
- quietExit :: MonadSh m => Int -> m a
- terror :: MonadSh m => Text -> m a
- bracket_sh :: Sh a -> (a -> Sh b) -> (a -> Sh c) -> Sh c
- catchany :: MonadBaseControl IO m => m a -> (SomeException -> m a) -> m 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
- catches_sh :: Sh a -> [Handler Sh a] -> Sh a
- catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh a
- toTextIgnore :: FilePath -> Text
- toTextWarn :: MonadSh m => FilePath -> m Text
- fromText :: Text -> FilePath
- whenM :: Monad m => m Bool -> m () -> m ()
- unlessM :: Monad m => m Bool -> m () -> m ()
- time :: MonadShControl m => m a -> m (Double, a)
- sleep :: MonadSh m => Int -> m ()
- liftIO :: MonadIO m => forall a. IO a -> m a
- when :: Monad m => Bool -> m () -> m ()
- unless :: Monad m => Bool -> m () -> m ()
- data FilePath :: *
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- get :: MonadSh m => m State
- put :: MonadSh m => State -> m ()
- 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
Documentation
class Monad m => MonadSh m where Source
MonadSh Sh | |
MonadSh m => MonadSh (ListT m) | |
MonadSh m => MonadSh (MaybeT m) | |
MonadSh m => MonadSh (IdentityT m) | |
MonadSh m => MonadSh (ContT r m) | |
MonadSh m => MonadSh (ReaderT r m) | |
MonadSh m => MonadSh (StateT s m) | |
MonadSh m => MonadSh (StateT s m) | |
(Error e, MonadSh m) => MonadSh (ErrorT e m) | |
(Monoid w, MonadSh m) => MonadSh (WriterT w m) | |
(Monoid w, MonadSh m) => MonadSh (WriterT w m) | |
(Monoid w, MonadSh m) => MonadSh (RWST r w s m) | |
(Monoid w, MonadSh m) => MonadSh (RWST r w s m) |
Entering Sh.
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.
print_stdout :: MonadShControl m => Bool -> m a -> m a Source
print_stderr :: MonadShControl m => Bool -> m a -> m a Source
print_commands :: MonadShControl m => Bool -> m a -> m a Source
log_stdout_with :: MonadShControl m => (Text -> IO ()) -> m a -> m a Source
log_stderr_with :: MonadShControl m => (Text -> IO ()) -> m a -> m a Source
Running external commands.
runFoldLines :: MonadSh m => a -> FoldCallback a -> FilePath -> [Text] -> m a Source
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
lastStderr :: MonadSh m => m Text Source
lastExitCode :: MonadSh m => m Int Source
For the variadic function cmd
partially applied variadic functions require type signatures
MonadSh m => ShellCmd (m ()) | |
(MonadSh m, (~) * s Text, Show s) => ShellCmd (m s) | |
MonadSh m => ShellCmd (m Text) | |
ShellCmd (Sh ()) | |
((~) * s Text, Show s) => ShellCmd (Sh s) | |
ShellCmd (Sh Text) | |
(CmdArg arg, ShellCmd result) => ShellCmd ([arg] -> result) | |
(CmdArg arg, ShellCmd result) => ShellCmd (arg -> result) |
Running commands Using handles
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
data StdStream :: *
Inherit | Inherit Handle from parent |
UseHandle Handle | Use the supplied Handle |
CreatePipe | Create a new pipe. The returned
|
Modifying and querying environment.
get_env_text :: MonadSh m => Text -> m Text Source
get_env_all :: MonadSh m => m [(String, String)] Source
appendToPath :: MonadSh m => FilePath -> m () Source
Environment directory
Printing
echo_n_err :: MonadSh m => Text -> m () Source
inspect_err :: (Show s, MonadSh m) => s -> m () Source
show_command :: FilePath -> [Text] -> Text Source
Querying filesystem.
Filename helpers
(</>) :: (ToFilePath filepath1, ToFilePath filepath2) => filepath1 -> filepath2 -> FilePath Source
uses System.FilePath.CurrentOS, but can automatically convert a Text
(<.>) :: ToFilePath filepath => filepath -> Text -> FilePath Source
uses System.FilePath.CurrentOS, but can automatically convert a Text
canonicalize :: MonadSh m => FilePath -> m FilePath Source
Obtain a (reasonably) canonic file path to a filesystem object. Based on "canonicalizePath" in system-fileio.
Manipulating filesystem.
reading/writing Files
readBinary :: MonadSh m => FilePath -> m ByteString Source
appendfile :: MonadSh m => FilePath -> Text -> m () Source
withTmpDir :: MonadShControl m => (FilePath -> m a) -> m a Source
exiting the program
Exceptions
bracket_sh :: Sh a -> (a -> Sh b) -> (a -> Sh c) -> Sh c Source
Deprecated: use Control.Exception.Lifted.bracket instead
catchany :: MonadBaseControl IO m => m a -> (SomeException -> m a) -> m a Source
catch_sh :: Exception e => Sh a -> (e -> Sh a) -> Sh a Source
Deprecated: use Control.Exception.Lifted.catch instead
handle_sh :: Exception e => (e -> Sh a) -> Sh a -> Sh a Source
Deprecated: use Control.Exception.Lifted.handle instead
handleany_sh :: (SomeException -> Sh a) -> Sh a -> Sh a Source
Deprecated: use Control.Exception.Enclosed.handleAny instead
finally_sh :: Sh a -> Sh b -> Sh a Source
Deprecated: use Control.Exception.Lifted.finally instead
catches_sh :: Sh a -> [Handler Sh a] -> Sh a Source
Deprecated: use Control.Exception.Lifted.catches instead
catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh a Source
Deprecated: use Control.Exception.Enclosed.catchAny instead
convert between Text and FilePath
toTextIgnore :: FilePath -> Text Source
silently uses the Right or Left value of "Filesystem.Path.CurrentOS.toText"
toTextWarn :: MonadSh m => FilePath -> m Text Source
Utility Functions
unlessM :: Monad m => m Bool -> m () -> m () Source
A monadic-conditional version of the unless
guard.
Re-exported for your convenience
when :: Monad m => Bool -> m () -> m ()
Conditional execution of monadic expressions. For example,
when debug (putStr "Debugging\n")
will output the string Debugging\n
if the Boolean value debug
is True
,
and otherwise do nothing.
data FilePath :: *
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
findFoldDirFilter :: (a -> FilePath -> Sh a) -> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a Source
like findDirFilterWhen
but use a folding function rather than a filter
The most general finder: you likely want a more specific one