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

Safe HaskellNone

Shelly.Lifted

Contents

Description

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

Documentation

class Monad m => MonadSh m whereSource

Methods

liftSh :: Sh a -> m aSource

Instances

MonadSh Sh 
MonadSh m => MonadSh (ListT m) 
MonadSh m => MonadSh (MaybeT m) 
MonadSh m => MonadSh (IdentityT m) 
MonadSh m => MonadSh (ContT r m) 
(Error e, MonadSh m) => MonadSh (ErrorT e m) 
MonadSh m => MonadSh (ReaderT r m) 
MonadSh m => MonadSh (StateT s m) 
MonadSh m => MonadSh (StateT s 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.

type ShIO a = Sh aSource

Deprecated: Use Sh instead of ShIO

ShIO is Deprecated in favor of Sh, which is easier to type.

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

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 aSource

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 aSource

sub :: MonadShControl m => m a -> m aSource

silently :: MonadShControl m => m a -> m aSource

verbosely :: MonadShControl m => m a -> m aSource

escaping :: MonadShControl m => Bool -> m a -> m aSource

print_stdout :: MonadShControl m => Bool -> m a -> m aSource

print_stderr :: MonadShControl m => Bool -> m a -> m aSource

print_commands :: MonadShControl m => Bool -> m a -> m aSource

tracing :: MonadShControl m => Bool -> m a -> m aSource

errExit :: MonadShControl m => Bool -> m a -> m aSource

Running external commands.

run :: MonadSh m => FilePath -> [Text] -> m TextSource

run_ :: MonadSh m => FilePath -> [Text] -> m ()Source

runFoldLines :: MonadSh m => a -> FoldCallback a -> FilePath -> [Text] -> m aSource

cmd :: ShellCmd result => FilePath -> resultSource

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 -> aSource

(-|-) :: (MonadShControl m, MonadSh m) => m Text -> m b -> m bSource

setStdin :: MonadSh m => Text -> m ()Source

command :: MonadSh m => FilePath -> [Text] -> [Text] -> m TextSource

command_ :: MonadSh m => FilePath -> [Text] -> [Text] -> m ()Source

command1 :: MonadSh m => FilePath -> [Text] -> Text -> [Text] -> m TextSource

command1_ :: MonadSh m => FilePath -> [Text] -> Text -> [Text] -> m ()Source

sshPairs :: MonadSh m => Text -> [(FilePath, [Text])] -> m TextSource

sshPairs_ :: MonadSh m => Text -> [(FilePath, [Text])] -> m ()Source

class ShellCmd t whereSource

For the variadic function cmd

partially applied variadic functions require type signatures

Methods

cmdAll :: FilePath -> [Text] -> tSource

Instances

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) 

class CmdArg a whereSource

Argument converter for the variadic argument version of run called cmd. Useful for a type signature of a function that uses cmd

Methods

toTextArg :: a -> TextSource

Running commands Using handles

runHandleSource

Arguments

:: MonadShControl m 
=> FilePath

command

-> [Text]

arguments

-> (Handle -> m a)

stdout handle

-> m a 

runHandlesSource

Arguments

:: MonadShControl m 
=> FilePath

command

-> [Text]

arguments

-> [StdHandle]

optionally connect process i/o handles to existing handles

-> (Handle -> Handle -> Handle -> m a)

stdin, stdout and stderr

-> m a 

transferFoldHandleLines :: a -> FoldCallback a -> Handle -> Handle -> IO aSource

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

Constructors

Inherit

Inherit Handle from parent

UseHandle Handle

Use the supplied Handle

CreatePipe

Create a new pipe. The returned Handle will use the default encoding and newline translation mode (just like Handles created by openFile).

Modifying and querying environment.

setenv :: MonadSh m => Text -> Text -> m ()Source

Environment directory

cd :: MonadSh m => FilePath -> m ()Source

chdir :: MonadShControl m => FilePath -> m a -> m aSource

Printing

echo :: MonadSh m => Text -> m ()Source

echo_n :: MonadSh m => Text -> m ()Source

echo_err :: MonadSh m => Text -> m ()Source

echo_n_err :: MonadSh m => Text -> m ()Source

inspect :: (Show s, MonadSh m) => s -> m ()Source

inspect_err :: (Show s, MonadSh m) => s -> m ()Source

tag :: (MonadShControl m, MonadSh m) => m a -> Text -> m aSource

trace :: MonadSh m => Text -> m ()Source

Querying filesystem.

Filename helpers

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

canonicalize :: MonadSh m => FilePath -> m FilePathSource

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

relativeToSource

Arguments

:: MonadSh m 
=> FilePath

anchor path, the prefix

-> FilePath

make this relative to anchor path

-> m FilePath 

hasExt :: Text -> FilePath -> BoolSource

flipped hasExtension for Text

Manipulating filesystem.

mv :: MonadSh m => FilePath -> FilePath -> m ()Source

rm :: MonadSh m => FilePath -> m ()Source

rm_f :: MonadSh m => FilePath -> m ()Source

rm_rf :: MonadSh m => FilePath -> m ()Source

cp :: MonadSh m => FilePath -> FilePath -> m ()Source

cp_r :: MonadSh m => FilePath -> FilePath -> m ()Source

mkdir :: MonadSh m => FilePath -> m ()Source

reading/writing Files

withTmpDir :: MonadShControl m => (FilePath -> m a) -> m aSource

exiting the program

exit :: MonadSh m => Int -> m aSource

quietExit :: MonadSh m => Int -> m aSource

terror :: MonadSh m => Text -> m aSource

Exceptions

bracket_sh :: Sh a -> (a -> Sh b) -> (a -> Sh c) -> Sh cSource

Deprecated: use Control.Exception.Lifted.bracket instead

catchany :: MonadBaseControl IO m => m a -> (SomeException -> m a) -> m aSource

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

Deprecated: use Control.Exception.Lifted.catch instead

handle_sh :: Exception e => (e -> Sh a) -> Sh a -> Sh aSource

Deprecated: use Control.Exception.Lifted.handle instead

handleany_sh :: (SomeException -> Sh a) -> Sh a -> Sh aSource

Deprecated: use Control.Exception.Enclosed.handleAny instead

finally_sh :: Sh a -> Sh b -> Sh aSource

Deprecated: use Control.Exception.Lifted.finally instead

catches_sh :: Sh a -> [Handler Sh a] -> Sh aSource

Deprecated: use Control.Exception.Lifted.catches instead

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

Deprecated: use Control.Exception.Enclosed.catchAny instead

convert between Text and FilePath

toTextIgnore :: FilePath -> TextSource

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

fromText :: Text -> FilePath

Convert human‐readable text into a FilePath.

This function ignores the user’s locale, and assumes all file paths are encoded in UTF8. If you need to create file paths with an unusual or obscure encoding, encode them manually and then use decode.

Since: 0.2

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 :: MonadShControl m => m a -> m (Double, a)Source

sleep :: MonadSh m => Int -> m ()Source

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.

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

An infix synonym for fmap.

internal functions for writing extensions

get :: MonadSh m => m StateSource

put :: MonadSh m => State -> m ()Source

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.

findFold :: (a -> FilePath -> Sh a) -> a -> FilePath -> Sh aSource

Fold an arbitrary folding function over files froma a find. Like findWhen but use a more general fold rather than a filter.

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.

findDirFilterWhenSource

Arguments

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