Safe Haskell | Safe-Infered |
---|
- Entering Sh.
- List functions
- Running external commands.
- Modifying and querying environment.
- Environment directory
- Printing
- Querying filesystem.
- Filename helpers
- Manipulating filesystem.
- reading/writing Files
- find functions
- exiting the program
- Exceptions
- convert between Text and FilePath
- Utilities.
- Re-exported for your convenience
- internal functions for writing extensions
This module is a wrapper for the module Shelly. The only difference is a main type Sh. In this module Sh contains a list of results. Actual definition of the type Sh is:
import qualified Shelly as S newtype Sh a = Sh { unSh :: S.Sh [a] }
This definition can simplify some filesystem commands. A monad bind operator becomes a pipe operator and we can write
findExt ext = findWhen (pure . hasExt ext) main :: IO () main = shs $ do mkdir "new" findExt "hs" "." >>= flip cp "new" findExt "cpp" "." >>= rm_f liftIO $ putStrLn "done"
Monad methods return and >>= behave like methods for
ListT Shelly.Sh
, but >> forgets the number of
the empty effects. So the last line prints "done"
only once.
I highly recommend 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 Data.Text.Lazy as LT default (LT.Text)
- data Sh a
- shs :: MonadIO m => Sh () -> m ()
- shelly :: MonadIO m => Sh a -> m [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_commands :: Bool -> Sh a -> Sh a
- roll :: Sh [a] -> Sh a
- unroll :: Sh a -> Sh [a]
- liftSh :: ([a] -> [b]) -> Sh a -> Sh b
- run :: FilePath -> [Text] -> Sh Text
- run_ :: FilePath -> [Text] -> Sh ()
- cmd :: ShellCommand result => FilePath -> result
- (-|-) :: Sh Text -> Sh b -> Sh b
- lastStderr :: Sh Text
- setStdin :: Text -> Sh ()
- 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
- sshPairs_ :: Text -> [(FilePath, [Text])] -> Sh ()
- setenv :: Text -> Text -> Sh ()
- get_env :: Text -> Sh (Maybe Text)
- get_env_text :: Text -> Sh Text
- getenv_def :: Text -> Text -> Sh Text
- appendToPath :: FilePath -> Sh ()
- cd :: FilePath -> Sh ()
- chdir :: FilePath -> Sh a -> Sh a
- pwd :: Sh FilePath
- echo, echo_n, echo_err, 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
- 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
- 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 ()
- readfile :: FilePath -> Sh Text
- writefile :: FilePath -> Text -> Sh ()
- appendfile :: FilePath -> Text -> Sh ()
- touchfile :: FilePath -> Sh ()
- withTmpDir :: (FilePath -> Sh a) -> Sh a
- 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
- exit :: Int -> Sh ()
- errorExit :: Text -> Sh ()
- terror :: Text -> Sh a
- catchany :: IO a -> (SomeException -> IO a) -> IO a
- catch_sh :: Exception e => Sh a -> (e -> Sh a) -> Sh a
- finally_sh :: Sh a -> Sh b -> Sh a
- data ShellyHandler a = forall e . Exception e => ShellyHandler (e -> Sh a)
- catches_sh :: Sh a -> [ShellyHandler a] -> Sh a
- catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh a
- toTextIgnore :: FilePath -> Text
- toTextWarn :: FilePath -> Sh Text
- fromText :: Text -> FilePath
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<$$>) :: Functor m => (b -> c) -> (a -> m b) -> a -> m c
- whenM :: Monad m => m Bool -> m () -> m ()
- unlessM :: Monad m => m Bool -> m () -> m ()
- time :: Sh a -> Sh (Double, a)
- liftIO :: MonadIO m => forall a. IO a -> m a
- when :: Monad m => Bool -> m () -> m ()
- unless :: Monad m => Bool -> m () -> m ()
- data FilePath
- get :: Sh State
- put :: State -> Sh ()
Entering Sh.
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.
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 aSource
Create a sub-Sh in which external command outputs are not echoed. Also commands are not printed. See sub.
verbosely :: Sh a -> Sh aSource
Create a sub-Sh in which external command outputs are echoed. Executed commands are printed See sub.
print_stdout :: Bool -> Sh a -> Sh aSource
Create a sub-Sh with stdout printing on or off
print_commands :: Bool -> Sh a -> Sh aSource
Create a sub-Sh with command echoing on or off
List functions
liftSh :: ([a] -> [b]) -> Sh a -> Sh bSource
Transform result as list. It can be useful for filtering.
Running external commands.
run :: FilePath -> [Text] -> Sh TextSource
Execute an external command. Takes the command name (no shell allowed,
just a name of something that can be found via PATH
; FIXME: setenv'd
PATH
is not taken into account when finding the exe name)
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 but still consume the result by using run_, If you want to avoid the memory and need to process the output then use runFoldLines.
run_ :: FilePath -> [Text] -> Sh ()Source
The same as run, but return () instead of the stdout content.
cmd :: ShellCommand result => FilePath -> resultSource
variadic argument version of 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.
a FilePath is converted to Text with toTextIgnore
.
You will need to add the following to your module:
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# OPTIONS_GHC -fno-warn-type-defaults #-} import Shelly import Data.Text.Lazy as LT default (LT.Text)
(-|-) :: Sh Text -> Sh b -> Sh bSource
Pipe operator. set the stdout the first command as the stdin of the second.
The output of last external command. See run.
sshPairs :: Text -> [(FilePath, [Text])] -> Sh TextSource
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: the commands will not be shell escaped.
Internally the list of commands are combined with the string && before given to ssh.
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 TextSource
Fetch the current value of an environment variable. Both empty and non-existent variables give empty string as a result.
getenv_def :: Text -> Text -> Sh TextSource
Fetch the current value of an environment variable. Both empty and non-existent variables give the default value as a result
appendToPath :: FilePath -> Sh ()Source
add the filepath onto the PATH env variable
FIXME: only effects the PATH once the process is ran, as per comments in which
Environment directory
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. This may have performance repercussions if you are doing hundreds of thousands of filesystem operations. You will want to handle these issues differently in those cases.
chdir :: FilePath -> Sh a -> Sh aSource
cd, execute a Sh action in the new directory and then pop back to the original directory
Printing
echo, echo_n, echo_err, 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.
inspect_err :: Show s => s -> Sh ()Source
a print lifted into Sh using stderr
show_command :: FilePath -> [Text] -> TextSource
Querying filesystem.
ls :: FilePath -> Sh FilePathSource
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 on PATH
, if exists. FIXME does not
respect setenv'd environment and uses findExecutable
which uses the PATH
inherited from the process
environment.
FIXME: findExecutable does not maintain a hash of existing commands and does a ton of file stats
Filename helpers
absPath :: FilePath -> Sh FilePathSource
Make a relative path absolute by combining with the working directory.
An absolute path is returned as is.
To create a relative path, use path
.
(</>) :: (ToFilePath filepath1, ToFilePath filepath2) => filepath1 -> filepath2 -> FilePathSource
uses System.FilePath.CurrentOS, but can automatically convert a Text
(<.>) :: ToFilePath filepath => filepath -> Text -> FilePathSource
uses System.FilePath.CurrentOS, but can automatically convert a Text
canonic :: FilePath -> Sh FilePathSource
makes an absolute path.
Like canonicalize
, but on an exception returns path
canonicalize :: FilePath -> Sh FilePathSource
Obtain a (reasonably) canonic file path to a filesystem object. Based on canonicalizePath in system-fileio.
relPath :: FilePath -> Sh FilePathSource
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
Manipulating filesystem.
mv :: FilePath -> FilePath -> Sh ()Source
Currently a renameFile wrapper. TODO: Support cross-filesystem move. TODO: Support directory paths in the second parameter, like in cp.
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 removeTree
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).
reading/writing Files
readfile :: FilePath -> Sh TextSource
(Strictly) read file into a Text. All other functions use Lazy Text. So Internally this reads a file as strict text and then converts it to lazy text, which is inefficient
withTmpDir :: (FilePath -> Sh a) -> Sh aSource
Create a temporary directory and pass it as a parameter to a Sh computation. The directory is nuked afterwards.
find functions
find :: FilePath -> Sh FilePathSource
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 FilePathSource
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 FilePathSource
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 aSource
like findDirFilterWhen
but use a folding function rather than a filter
The most general finder: you likely want a more specific one
exiting the program
Exceptions
catchany :: IO a -> (SomeException -> IO a) -> IO aSource
A helper to catch any exception (same as
...
).
catch
(e :: SomeException) -> ...
finally_sh :: Sh a -> Sh b -> Sh aSource
Catch an exception in the Sh monad.
data ShellyHandler a Source
You need this when using catches_sh
.
forall e . Exception e => ShellyHandler (e -> Sh a) |
catches_sh :: Sh a -> [ShellyHandler a] -> Sh aSource
Catch multiple exceptions in the Sh monad.
catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh aSource
Catch an exception in the Sh monad.
convert between Text and FilePath
toTextIgnore :: FilePath -> TextSource
silently uses the Right or Left value of Filesystem.Path.CurrentOS.toText
toTextWarn :: FilePath -> Sh TextSource
Utilities.
(<$$>) :: Functor m => (b -> c) -> (a -> m b) -> a -> m cSource
A functor-lifting function composition.
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