shelly-0.9.2: shell-like (systems) programming in Haskell

Safe HaskellSafe-Infered

Shelly

Contents

Description

A module for shell-like / perl-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 ShIO maintains its own environment and its own working directory.

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 Data.Text.Lazy as LT
 default (LT.Text)

Synopsis

Entering ShIO.

type ShIO a = ReaderT (IORef State) IO aSource

shelly :: MonadIO m => ShIO a -> m aSource

Enter a ShIO 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 ShIO.

sub :: ShIO a -> ShIO aSource

Enter a sub-ShIO that inherits the environment The original state will be restored when the sub-ShIO completes. Exceptions are propagated normally.

silently :: ShIO a -> ShIO aSource

Create a sub-ShIO in which external command outputs are not echoed. Also commands are not printed. See sub.

verbosely :: ShIO a -> ShIO aSource

Create a sub-ShIO in which external command outputs are echoed. Executed commands are printed See sub.

print_stdout :: Bool -> ShIO a -> ShIO aSource

Turn on/off printing stdout

print_commands :: Bool -> ShIO a -> ShIO aSource

Turn on/off command echoing.

Running external commands.

run :: FilePath -> [Text] -> ShIO 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.

cmd :: ShellCommand result => FilePath -> resultSource

variadic argument version of run. The syntax is more convenient but it also allows the use of a FilePath as an argument. 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)

(-|-) :: ShIO Text -> ShIO b -> ShIO bSource

Pipe operator. set the stdout the first command as the stdin of the second.

lastStderr :: ShIO TextSource

The output of last external command. See run.

setStdin :: Text -> ShIO ()Source

set the stdin to be used and cleared by the next run.

command :: FilePath -> [Text] -> [Text] -> ShIO TextSource

bind some arguments to run for re-use Example: monit = command monit [-c, monitrc]

command_ :: FilePath -> [Text] -> [Text] -> ShIO ()Source

bind some arguments to run_ for re-use Example: monit_ = command_ monit [-c, monitrc]

command1 :: FilePath -> [Text] -> Text -> [Text] -> ShIO TextSource

bind some arguments to run for re-use, and expect 1 argument Example: git = command1 git []; git pull [origin, master]

command1_ :: FilePath -> [Text] -> Text -> [Text] -> ShIO ()Source

bind some arguments to run for re-use, and expect 1 argument Example: git_ = command1_ git []; git+ pull [origin, master]

Modifying and querying environment.

setenv :: Text -> Text -> ShIO ()Source

Set an environment variable. The environment is maintained in ShIO internally, and is passed to any external commands to be executed.

getenv :: Text -> ShIO 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 -> ShIO TextSource

Fetch the current value of an environment variable. Both empty and non-existent variables give the default value as a result

appendToPath :: FilePath -> ShIO ()Source

add the filepath onto the PATH env variable FIXME: see comments for which

Environment directory

cd :: FilePath -> ShIO ()Source

Change current working directory of ShIO. This does *not* change the working directory of the process we are running it. Instead, ShIO keeps track of its own workking 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 -> ShIO a -> ShIO aSource

cd, execute a ShIO action in the new directory and then pop back to the original directory

pwd :: ShIO FilePathSource

Obtain the current (ShIO) working directory.

Printing

echo, echo_n_err, echo_err, echo_n :: Text -> ShIO ()Source

Echo text to standard (error, when using _err variants) output. The _n variants do not print a final newline.

inspect :: Show s => s -> ShIO ()Source

a print lifted into ShIO

tag :: ShIO a -> Text -> ShIO aSource

same as trace, but use it combinator style

trace :: Text -> ShIO ()Source

log actions that occur

Querying filesystem.

ls :: FilePath -> ShIO [FilePath]Source

List directory contents. Does *not* include "." and "..", but it does include (other) hidden files.

ls' :: FilePath -> ShIO [Text]Source

Get back [Text] instead of [FilePath]

test_e :: FilePath -> ShIO BoolSource

Does a path point to an existing filesystem object?

test_f :: FilePath -> ShIO BoolSource

Does a path point to an existing file?

test_d :: FilePath -> ShIO BoolSource

Does a path point to an existing directory?

test_s :: FilePath -> ShIO BoolSource

Does a path point to a symlink?

which :: FilePath -> ShIO (Maybe FilePath)Source

Get a full path to an executable on PATH, if exists. FIXME does not respect setenv'd environment and uses PATH inherited from the process environment.

find :: FilePath -> ShIO [FilePath]Source

List directory recursively (like the POSIX utility find).

Filename helpers

path :: FilePath -> ShIO FilePathSource

makes an absolute path. Same as canonic. TODO: use normalise from system-filepath

absPath :: FilePath -> ShIO FilePathSource

makes an absolute path. path will also normalize

(</>) :: (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

Manipulating filesystem.

mv :: FilePath -> FilePath -> ShIO ()Source

Currently a renameFile wrapper. TODO: Support cross-filesystem move. TODO: Support directory paths in the second parameter, like in cp.

rm_f :: FilePath -> ShIO ()Source

Remove a file. Does not fail if the file already is not there. Does fail if the file is not a file.

rm_rf :: FilePath -> ShIO ()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.

cp :: FilePath -> FilePath -> ShIO ()Source

Copy a file. The second path could be a directory, in which case the original file name is used, in that directory.

cp_r :: FilePath -> FilePath -> ShIO ()Source

Copy a file, or a directory recursively.

mkdir :: FilePath -> ShIO ()Source

Create a new directory (fails if the directory exists).

mkdir_p :: FilePath -> ShIO ()Source

Create a new directory, including parents (succeeds if the directory already exists).

readfile :: FilePath -> ShIO 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

writefile :: FilePath -> Text -> ShIO ()Source

Write a Lazy Text to a file.

appendfile :: FilePath -> Text -> ShIO ()Source

Append a Lazy Text to a file.

withTmpDir :: (FilePath -> ShIO a) -> ShIO aSource

Create a temporary directory and pass it as a parameter to a ShIO computation. The directory is nuked afterwards.

Running external commands asynchronously.

jobs :: Int -> (BgJobManager -> ShIO a) -> ShIO aSource

Create a BgJobManager which has a limit on the max number of background tasks. an invocation of jobs is independent of any others, and not tied to the ShIO monad in any way. This blocks the execution of the program until all background jobs are finished.

background :: BgJobManager -> ShIO a -> ShIO (BgResult a)Source

Run the ShIO task asynchronously in the background, returns the `BgResult a`, a promise immediately. Run getBgResult to wait for the result. The background task will inherit the current ShIO context The BjJobManager ensures the max jobs limit must be sufficient for the parent and all children.

getBgResult :: BgResult a -> ShIO aSource

Returns the promised result from a backgrounded task. Blocks until the task completes.

data BgResult a Source

Type returned by tasks run asynchronously in the background.

exiting the program

terror :: Text -> ShIO aSource

fail that takes a Text

Utilities.

(<$>) :: Functor f => (a -> b) -> f a -> f b

An infix synonym for fmap.

(<$$>) :: Functor m => (b -> c) -> (a -> m b) -> a -> m cSource

A functor-lifting function composition.

grep :: PredicateLike pattern hay => pattern -> [hay] -> [hay]Source

Like filter, but more conveniently used with String lists, where a substring match (TODO: also provide globs) is expressed as grep "needle" [ "the", "stack", "of", "hay" ]. Boolean predicates just like with filter are supported too: grep ("fun" isPrefixOf) [...].

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.

canonic :: FilePath -> ShIO FilePathSource

Obtain a (reasonably) canonic file path to a filesystem object. Based on canonicalizePath in FileSystem.

catchany :: IO a -> (SomeException -> IO a) -> IO aSource

A helper to catch any exception (same as ... catch (e :: SomeException) -> ...).

catch_sh :: Exception e => ShIO a -> (e -> ShIO a) -> ShIO aSource

Catch an exception in the ShIO monad.

catchany_sh :: ShIO a -> (SomeException -> ShIO a) -> ShIO aSource

Catch an exception in the ShIO monad.

data Timing Source

Constructors

Timing Double 

time :: ShIO a -> ShIO (Timing, a)Source

Run a ShIO computation and collect timing information.

convert between Text and FilePath

toTextIgnore :: FilePath -> TextSource

silently uses the Right or Left value of Filesystem.Path.CurrentOS.toText

Re-exported for your convenience

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

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.

unless :: Monad m => Bool -> m () -> m ()

The reverse of when.