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

Safe HaskellNone
LanguageHaskell98

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 where Source #

Minimal complete definition

liftSh

Methods

liftSh :: Sh a -> m a Source #

Instances

MonadSh Sh Source # 

Methods

liftSh :: Sh a -> Sh a Source #

MonadSh m => MonadSh (ListT m) Source # 

Methods

liftSh :: Sh a -> ListT m a Source #

MonadSh m => MonadSh (MaybeT m) Source # 

Methods

liftSh :: Sh a -> MaybeT m a Source #

(Monoid w, MonadSh m) => MonadSh (WriterT w m) Source # 

Methods

liftSh :: Sh a -> WriterT w m a Source #

MonadSh m => MonadSh (StateT s m) Source # 

Methods

liftSh :: Sh a -> StateT s m a Source #

(Error e, MonadSh m) => MonadSh (ErrorT e m) Source # 

Methods

liftSh :: Sh a -> ErrorT e m a Source #

MonadSh m => MonadSh (IdentityT * m) Source # 

Methods

liftSh :: Sh a -> IdentityT * m a Source #

MonadSh m => MonadSh (StateT s m) Source # 

Methods

liftSh :: Sh a -> StateT s m a Source #

(Monoid w, MonadSh m) => MonadSh (WriterT w m) Source # 

Methods

liftSh :: Sh a -> WriterT w m a Source #

MonadSh m => MonadSh (ReaderT * r m) Source # 

Methods

liftSh :: Sh a -> ReaderT * r m a Source #

MonadSh m => MonadSh (ContT * r m) Source # 

Methods

liftSh :: Sh a -> ContT * r m a Source #

(Monoid w, MonadSh m) => MonadSh (RWST r w s m) Source # 

Methods

liftSh :: Sh a -> RWST r w s m a Source #

(Monoid w, MonadSh m) => MonadSh (RWST r w s m) Source # 

Methods

liftSh :: Sh a -> RWST r w s m a Source #

class Monad m => MonadShControl m where Source #

Minimal complete definition

liftShWith, restoreSh

Associated Types

data ShM m a :: * Source #

Methods

liftShWith :: ((forall x. m x -> Sh (ShM m x)) -> Sh a) -> m a Source #

restoreSh :: ShM m a -> m a Source #

Instances

MonadShControl Sh Source # 

Associated Types

data ShM (Sh :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. Sh x -> Sh (ShM Sh x)) -> Sh a) -> Sh a Source #

restoreSh :: ShM Sh a -> Sh a Source #

MonadShControl m => MonadShControl (ListT m) Source # 

Associated Types

data ShM (ListT m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. ListT m x -> Sh (ShM (ListT m) x)) -> Sh a) -> ListT m a Source #

restoreSh :: ShM (ListT m) a -> ListT m a Source #

MonadShControl m => MonadShControl (MaybeT m) Source # 

Associated Types

data ShM (MaybeT m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. MaybeT m x -> Sh (ShM (MaybeT m) x)) -> Sh a) -> MaybeT m a Source #

restoreSh :: ShM (MaybeT m) a -> MaybeT m a Source #

(MonadShControl m, Monoid w) => MonadShControl (WriterT w m) Source # 

Associated Types

data ShM (WriterT w m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. WriterT w m x -> Sh (ShM (WriterT w m) x)) -> Sh a) -> WriterT w m a Source #

restoreSh :: ShM (WriterT w m) a -> WriterT w m a Source #

MonadShControl m => MonadShControl (StateT s m) Source # 

Associated Types

data ShM (StateT s m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. StateT s m x -> Sh (ShM (StateT s m) x)) -> Sh a) -> StateT s m a Source #

restoreSh :: ShM (StateT s m) a -> StateT s m a Source #

(MonadShControl m, Error e) => MonadShControl (ErrorT e m) Source # 

Associated Types

data ShM (ErrorT e m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. ErrorT e m x -> Sh (ShM (ErrorT e m) x)) -> Sh a) -> ErrorT e m a Source #

restoreSh :: ShM (ErrorT e m) a -> ErrorT e m a Source #

MonadShControl m => MonadShControl (IdentityT * m) Source # 

Associated Types

data ShM (IdentityT * m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. IdentityT * m x -> Sh (ShM (IdentityT * m) x)) -> Sh a) -> IdentityT * m a Source #

restoreSh :: ShM (IdentityT * m) a -> IdentityT * m a Source #

MonadShControl m => MonadShControl (StateT s m) Source # 

Associated Types

data ShM (StateT s m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. StateT s m x -> Sh (ShM (StateT s m) x)) -> Sh a) -> StateT s m a Source #

restoreSh :: ShM (StateT s m) a -> StateT s m a Source #

(MonadShControl m, Monoid w) => MonadShControl (WriterT w m) Source # 

Associated Types

data ShM (WriterT w m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. WriterT w m x -> Sh (ShM (WriterT w m) x)) -> Sh a) -> WriterT w m a Source #

restoreSh :: ShM (WriterT w m) a -> WriterT w m a Source #

MonadShControl m => MonadShControl (ReaderT * r m) Source # 

Associated Types

data ShM (ReaderT * r m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. ReaderT * r m x -> Sh (ShM (ReaderT * r m) x)) -> Sh a) -> ReaderT * r m a Source #

restoreSh :: ShM (ReaderT * r m) a -> ReaderT * r m a Source #

(MonadShControl m, Monoid w) => MonadShControl (RWST r w s m) Source # 

Associated Types

data ShM (RWST r w s m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. RWST r w s m x -> Sh (ShM (RWST r w s m) x)) -> Sh a) -> RWST r w s m a Source #

restoreSh :: ShM (RWST r w s m) a -> RWST r w s m a Source #

(MonadShControl m, Monoid w) => MonadShControl (RWST r w s m) Source # 

Associated Types

data ShM (RWST r w s m :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. RWST r w s m x -> Sh (ShM (RWST r w s m) x)) -> Sh a) -> RWST r w s m a Source #

restoreSh :: ShM (RWST r w s m) a -> RWST r w s m a Source #

Entering Sh.

data Sh a Source #

Instances

Monad Sh Source # 

Methods

(>>=) :: Sh a -> (a -> Sh b) -> Sh b #

(>>) :: Sh a -> Sh b -> Sh b #

return :: a -> Sh a #

fail :: String -> Sh a #

Functor Sh Source # 

Methods

fmap :: (a -> b) -> Sh a -> Sh b #

(<$) :: a -> Sh b -> Sh a #

Applicative Sh Source # 

Methods

pure :: a -> Sh a #

(<*>) :: Sh (a -> b) -> Sh a -> Sh b #

(*>) :: Sh a -> Sh b -> Sh b #

(<*) :: Sh a -> Sh b -> Sh a #

MonadIO Sh Source # 

Methods

liftIO :: IO a -> Sh a #

MonadThrow Sh Source # 

Methods

throwM :: Exception e => e -> Sh a #

MonadCatch Sh Source # 

Methods

catch :: Exception e => Sh a -> (e -> Sh a) -> Sh a #

MonadMask Sh Source # 

Methods

mask :: ((forall a. Sh a -> Sh a) -> Sh b) -> Sh b #

uninterruptibleMask :: ((forall a. Sh a -> Sh a) -> Sh b) -> Sh b #

MonadShControl Sh Source # 

Associated Types

data ShM (Sh :: * -> *) a :: * Source #

Methods

liftShWith :: ((forall x. Sh x -> Sh (ShM Sh x)) -> Sh a) -> Sh a Source #

restoreSh :: ShM Sh a -> Sh a Source #

MonadSh Sh Source # 

Methods

liftSh :: Sh a -> Sh a Source #

MonadBase IO Sh Source # 

Methods

liftBase :: IO α -> Sh α #

MonadBaseControl IO Sh Source # 

Associated Types

type StM (Sh :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase Sh IO -> IO a) -> Sh a #

restoreM :: StM Sh a -> Sh a #

ShellCmd (Sh ()) Source # 

Methods

cmdAll :: FilePath -> [Text] -> Sh () Source #

((~) * s Text, Show s) => ShellCmd (Sh s) Source # 

Methods

cmdAll :: FilePath -> [Text] -> Sh s Source #

ShellCmd (Sh Text) Source # 

Methods

cmdAll :: FilePath -> [Text] -> Sh Text Source #

data ShM Sh Source # 
data ShM Sh = ShSh a
type StM Sh a Source # 
type StM Sh a

type ShIO a = Sh a Source #

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.

sub :: MonadShControl m => m a -> m a Source #

silently :: MonadShControl m => m a -> m a Source #

verbosely :: MonadShControl m => m a -> m a Source #

escaping :: MonadShControl m => Bool -> m a -> m a Source #

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 #

tracing :: MonadShControl m => Bool -> m a -> m a Source #

errExit :: 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.

run :: MonadSh m => FilePath -> [Text] -> m Text Source #

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

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 #

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

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

command :: MonadSh m => FilePath -> [Text] -> [Text] -> m Text Source #

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

command1 :: MonadSh m => FilePath -> [Text] -> Text -> [Text] -> m Text Source #

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

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

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

class ShellCmd t where Source #

For the variadic function cmd

partially applied variadic functions require type signatures

Minimal complete definition

cmdAll

Methods

cmdAll :: FilePath -> [Text] -> t Source #

Instances

ShellCmd (Sh ()) Source # 

Methods

cmdAll :: FilePath -> [Text] -> Sh () Source #

((~) * s Text, Show s) => ShellCmd (Sh s) Source # 

Methods

cmdAll :: FilePath -> [Text] -> Sh s Source #

ShellCmd (Sh Text) Source # 

Methods

cmdAll :: FilePath -> [Text] -> Sh Text Source #

(CmdArg arg, ShellCmd result) => ShellCmd ([arg] -> result) Source # 

Methods

cmdAll :: FilePath -> [Text] -> [arg] -> result Source #

(CmdArg arg, ShellCmd result) => ShellCmd (arg -> result) Source # 

Methods

cmdAll :: FilePath -> [Text] -> arg -> result Source #

class CmdArg a where Source #

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

Minimal complete definition

toTextArg

Methods

toTextArg :: a -> Text Source #

Running commands Using handles

runHandle Source #

Arguments

:: MonadShControl m 
=> FilePath

command

-> [Text]

arguments

-> (Handle -> m a)

stdout handle

-> m a 

runHandles Source #

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

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).

NoStream

No stream handle will be passed

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 a Source #

chdir_p :: MonadShControl m => FilePath -> m a -> m a Source #

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 a Source #

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

Querying filesystem.

lsT :: MonadSh m => FilePath -> m [Text] Source #

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.

relativeTo Source #

Arguments

:: MonadSh m 
=> FilePath

anchor path, the prefix

-> FilePath

make this relative to anchor path

-> m FilePath 

hasExt :: Text -> FilePath -> Bool Source #

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 #

mkdir_p :: MonadSh m => FilePath -> m () Source #

reading/writing Files

writefile :: MonadSh m => FilePath -> Text -> m () Source #

appendfile :: MonadSh m => FilePath -> Text -> m () Source #

withTmpDir :: MonadShControl m => (FilePath -> m a) -> m a Source #

exiting the program

exit :: MonadSh m => Int -> m a Source #

errorExit :: MonadSh m => Text -> m a Source #

quietExit :: MonadSh m => Int -> m a Source #

terror :: MonadSh m => Text -> m a Source #

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"

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

data FilePath :: * #

Instances

Eq FilePath 
Data FilePath 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilePath -> c FilePath #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilePath #

toConstr :: FilePath -> Constr #

dataTypeOf :: FilePath -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FilePath) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilePath) #

gmapT :: (forall b. Data b => b -> b) -> FilePath -> FilePath #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilePath -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilePath -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilePath -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilePath -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilePath -> m FilePath #

Ord FilePath 
NFData FilePath 

Methods

rnf :: FilePath -> () #

CmdArg FilePath Source # 

(<$>) :: 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 Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an 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

get :: MonadSh m => m State Source #

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 a Source #

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.

findDirFilterWhen Source #

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 a Source #

like findDirFilterWhen but use a folding function rather than a filter The most general finder: you likely want a more specific one

followSymlink :: MonadShControl m => Bool -> m a -> m a Source #

Orphan instances

MonadSh m => ShellCmd (m ()) Source # 

Methods

cmdAll :: FilePath -> [Text] -> m () Source #

(MonadSh m, (~) * s Text, Show s) => ShellCmd (m s) Source # 

Methods

cmdAll :: FilePath -> [Text] -> m s Source #

MonadSh m => ShellCmd (m Text) Source # 

Methods

cmdAll :: FilePath -> [Text] -> m Text Source #