shelly-1.12.1: shell-like (systems) programming in Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Shelly.Lifted

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 #

Methods

liftSh :: Sh a -> m a #

Instances

Instances details
MonadSh Sh # 
Instance details

Defined in Shelly.Lifted

Methods

liftSh :: Sh a -> Sh a #

MonadSh m => MonadSh (MaybeT m) # 
Instance details

Defined in Shelly.Lifted

Methods

liftSh :: Sh a -> MaybeT m a #

MonadSh m => MonadSh (ExceptT e m) # 
Instance details

Defined in Shelly.Lifted

Methods

liftSh :: Sh a -> ExceptT e m a #

MonadSh m => MonadSh (IdentityT m) # 
Instance details

Defined in Shelly.Lifted

Methods

liftSh :: Sh a -> IdentityT m a #

MonadSh m => MonadSh (ReaderT r m) # 
Instance details

Defined in Shelly.Lifted

Methods

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

MonadSh m => MonadSh (StateT s m) # 
Instance details

Defined in Shelly.Lifted

Methods

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

MonadSh m => MonadSh (StateT s m) # 
Instance details

Defined in Shelly.Lifted

Methods

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

(Monoid w, MonadSh m) => MonadSh (WriterT w m) # 
Instance details

Defined in Shelly.Lifted

Methods

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

(Monoid w, MonadSh m) => MonadSh (WriterT w m) # 
Instance details

Defined in Shelly.Lifted

Methods

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

MonadSh m => MonadSh (ContT r m) # 
Instance details

Defined in Shelly.Lifted

Methods

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

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

Defined in Shelly.Lifted

Methods

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

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

Defined in Shelly.Lifted

Methods

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

class Monad m => MonadShControl m where #

Associated Types

data ShM m a #

Methods

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

restoreSh :: ShM m a -> m a #

Instances

Instances details
MonadShControl Sh # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM Sh a #

Methods

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

restoreSh :: ShM Sh a -> Sh a #

MonadShControl m => MonadShControl (MaybeT m) # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM (MaybeT m) a #

Methods

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

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

MonadShControl m => MonadShControl (ExceptT e m) # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM (ExceptT e m) a #

Methods

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

restoreSh :: ShM (ExceptT e m) a -> ExceptT e m a #

MonadShControl m => MonadShControl (IdentityT m) # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM (IdentityT m) a #

Methods

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

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

MonadShControl m => MonadShControl (ReaderT r m) # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM (ReaderT r m) a #

Methods

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

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

MonadShControl m => MonadShControl (StateT s m) # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM (StateT s m) a #

Methods

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

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

MonadShControl m => MonadShControl (StateT s m) # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM (StateT s m) a #

Methods

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

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

(MonadShControl m, Monoid w) => MonadShControl (WriterT w m) # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM (WriterT w m) a #

Methods

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

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

(MonadShControl m, Monoid w) => MonadShControl (WriterT w m) # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM (WriterT w m) a #

Methods

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

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

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

Defined in Shelly.Lifted

Associated Types

data ShM (RWST r w s m) a #

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 #

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

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

Defined in Shelly.Lifted

Associated Types

data ShM (RWST r w s m) a #

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 #

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

Entering Sh

data Sh a #

Instances

Instances details
MonadFail Sh # 
Instance details

Defined in Shelly.Base

Methods

fail :: String -> Sh a

MonadIO Sh # 
Instance details

Defined in Shelly.Base

Methods

liftIO :: IO a -> Sh a #

Applicative Sh # 
Instance details

Defined in Shelly.Base

Methods

pure :: a -> Sh a

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

liftA2 :: (a -> b -> c) -> Sh a -> Sh b -> Sh c

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

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

Functor Sh # 
Instance details

Defined in Shelly.Base

Methods

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

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

Monad Sh # 
Instance details

Defined in Shelly.Base

Methods

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

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

return :: a -> Sh a

MonadCatch Sh # 
Instance details

Defined in Shelly.Base

Methods

catch :: (HasCallStack, Exception e) => Sh a -> (e -> Sh a) -> Sh a

MonadMask Sh # 
Instance details

Defined in Shelly.Base

Methods

mask :: HasCallStack => ((forall a. Sh a -> Sh a) -> Sh b) -> Sh b

uninterruptibleMask :: HasCallStack => ((forall a. Sh a -> Sh a) -> Sh b) -> Sh b

generalBracket :: HasCallStack => Sh a -> (a -> ExitCase b -> Sh c) -> (a -> Sh b) -> Sh (b, c)

MonadThrow Sh # 
Instance details

Defined in Shelly.Base

Methods

throwM :: (HasCallStack, Exception e) => e -> Sh a

MonadSh Sh # 
Instance details

Defined in Shelly.Lifted

Methods

liftSh :: Sh a -> Sh a #

MonadShControl Sh # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM Sh a #

Methods

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

restoreSh :: ShM Sh a -> Sh a #

MonadBaseControl IO Sh # 
Instance details

Defined in Shelly.Base

Associated Types

type StM Sh a #

Methods

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

restoreM :: StM Sh a -> Sh a #

MonadBase IO Sh # 
Instance details

Defined in Shelly.Base

Methods

liftBase :: IO α -> Sh α #

ShellCmd (Sh Text) # 
Instance details

Defined in Shelly

Methods

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

s ~ () => ShellCmd (Sh s) # 
Instance details

Defined in Shelly

Methods

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

newtype ShM Sh a # 
Instance details

Defined in Shelly.Lifted

newtype ShM Sh a = ShSh a
type StM Sh a # 
Instance details

Defined in Shelly.Base

type StM Sh a

type ShIO a = Sh a #

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 #

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 #

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 #

Using this entry point creates a .shelly directory in the case of failure where errors are recorded.

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 #

print_commands_with :: MonadShControl m => (Text -> IO ()) -> m a -> m a #

Since: 1.12.1

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 #

Running external commands

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 #

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 #

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

For the variadic function cmd.

Partially applied variadic functions require type signatures.

Methods

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

Instances

Instances details
ShellCmd (Sh Text) # 
Instance details

Defined in Shelly

Methods

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

s ~ () => ShellCmd (Sh s) # 
Instance details

Defined in Shelly

Methods

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

MonadSh m => ShellCmd (m Text) # 
Instance details

Defined in Shelly.Lifted

Methods

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

MonadSh m => ShellCmd (m ()) # 
Instance details

Defined in Shelly.Lifted

Methods

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

(MonadSh m, s ~ Text, Show s) => ShellCmd (m s) # 
Instance details

Defined in Shelly.Lifted

Methods

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

(CmdArg arg, ShellCmd result) => ShellCmd (arg -> result) # 
Instance details

Defined in Shelly

Methods

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

class CmdArg a where #

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

Methods

toTextArgs :: a -> [Text] #

Since: 1.12.0

Instances

Instances details
CmdArg Text # 
Instance details

Defined in Shelly

Methods

toTextArgs :: Text -> [Text] #

CmdArg String # 
Instance details

Defined in Shelly

Methods

toTextArgs :: String -> [Text] #

CmdArg a => CmdArg [a] # 
Instance details

Defined in Shelly

Methods

toTextArgs :: [a] -> [Text] #

Running commands Using handles

runHandle #

Arguments

:: MonadShControl m 
=> FilePath

command

-> [Text]

arguments

-> (Handle -> m a)

stdout handle

-> m a 

runHandles #

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 

transferLinesAndCombine :: MonadIO m => Handle -> (Text -> IO ()) -> m Text #

transferFoldHandleLines :: a -> FoldCallback a -> Handle -> (Text -> IO ()) -> IO a #

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 
UseHandle Handle 
CreatePipe 
NoStream 

Instances

Instances details
Show StdStream 
Instance details

Defined in System.Process.Common

Methods

showsPrec :: Int -> StdStream -> ShowS

show :: StdStream -> String

showList :: [StdStream] -> ShowS

Eq StdStream 
Instance details

Defined in System.Process.Common

Methods

(==) :: StdStream -> StdStream -> Bool

(/=) :: StdStream -> StdStream -> Bool

Modifying and querying environment

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 () #

Environment directory

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 #

Printing

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

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

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

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

echoWith :: MonadSh m => (Text -> IO ()) -> Text -> m () #

Since: 1.12.1

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 #

Querying filesystem

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

Filename helpers

(</>) :: (ToFilePath filepath1, ToFilePath filepath2) => filepath1 -> filepath2 -> FilePath #

Uses System.FilePath, but can automatically convert a Text.

(<.>) :: ToFilePath filepath => filepath -> Text -> FilePath #

Uses System.FilePath, but can automatically convert a Text.

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

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

relativeTo #

Arguments

:: MonadSh m 
=> FilePath

anchor path, the prefix

-> FilePath

make this relative to anchor path

-> m FilePath 

hasExt :: Text -> FilePath -> Bool #

Flipped hasExtension for Text.

Manipulating filesystem

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 () #

reading/writing Files

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 #

exiting the program

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

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

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

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

Exceptions

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

Deprecated: use Control.Exception.Lifted.bracket instead

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

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

Deprecated: use Control.Exception.Lifted.catch instead

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

Deprecated: use Control.Exception.Lifted.handle instead

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

Deprecated: use Control.Exception.Enclosed.handleAny instead

finally_sh :: Sh a -> Sh b -> Sh a #

Deprecated: use Control.Exception.Lifted.finally instead

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

Deprecated: use Control.Exception.Lifted.catches instead

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

Deprecated: use Control.Exception.Enclosed.catchAny instead

convert between Text and FilePath

toTextWarn :: MonadSh m => FilePath -> m Text #

fromText :: Text -> FilePath #

Convert Text to a FilePath.

Utility Functions

whenM :: Monad m => m Bool -> m () -> m () #

A monadic-conditional version of the when guard.

unlessM :: Monad m => m Bool -> m () -> m () #

A monadic-conditional version of the unless guard.

time :: MonadShControl m => m a -> m (Double, a) #

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

Re-exported for your convenience

liftIO :: MonadIO m => IO a -> m a #

when :: Applicative f => Bool -> f () -> f () #

unless :: Applicative f => Bool -> f () -> f () #

type FilePath = String #

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

internal functions for writing extensions

get :: MonadSh m => m State #

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

find functions

find :: FilePath -> Sh [FilePath] #

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] #

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 #

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] #

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 #

Arguments

:: (FilePath -> Sh Bool)

directory filter

-> (FilePath -> Sh Bool)

file filter

-> FilePath

directory

-> Sh [FilePath] 

Similar to 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 #

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 #

Orphan instances

MonadSh m => ShellCmd (m Text) # 
Instance details

Methods

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

MonadSh m => ShellCmd (m ()) # 
Instance details

Methods

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

(MonadSh m, s ~ Text, Show s) => ShellCmd (m s) # 
Instance details

Methods

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