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

Safe HaskellNone
LanguageHaskell98

Shelly.Pipe

Contents

Description

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.

Documentation in this module mostly just reference documentation from the main Shelly module.

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
import Shelly
import Data.Text as T
default (T.Text)

Synopsis

Entering Sh.

data Sh a #

This type is a simple wrapper for a type Shelly.Sh. Sh contains a list of results.

Instances

Monad Sh # 

Methods

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

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

return :: a -> Sh a #

fail :: String -> Sh a #

Functor Sh # 

Methods

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

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

Applicative Sh # 

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 # 

Methods

liftIO :: IO a -> Sh a #

Alternative Sh # 

Methods

empty :: Sh a #

(<|>) :: Sh a -> Sh a -> Sh a #

some :: Sh a -> Sh [a] #

many :: Sh a -> Sh [a] #

MonadPlus Sh # 

Methods

mzero :: Sh a #

mplus :: Sh a -> Sh a -> Sh a #

shs :: MonadIO m => Sh () -> m () #

Performs shelly and then an empty action return ().

shelly :: MonadIO m => Sh a -> m [a] #

see shelly

shellyFailDir :: MonadIO m => Sh a -> m [a] #

shsFailDir :: MonadIO m => Sh () -> m () #

Performs shellyFailDir and then an empty action return ().

sub :: Sh a -> Sh a #

see sub

silently :: Sh a -> Sh a #

verbosely :: Sh a -> Sh a #

escaping :: Bool -> Sh a -> Sh a #

print_commands :: Bool -> Sh a -> Sh a #

see 'S.print_commands

tracing :: Bool -> Sh a -> Sh a #

errExit :: Bool -> Sh a -> Sh a #

log_stdout_with :: (Text -> IO ()) -> Sh a -> Sh a #

log_stderr_with :: (Text -> IO ()) -> Sh a -> Sh a #

List functions

roll :: Sh [a] -> Sh a #

Pack list of results. It performs concat inside Sh.

unroll :: Sh a -> Sh [a] #

Unpack list of results.

liftSh :: ([a] -> [b]) -> Sh a -> Sh b #

Transform result as list. It can be useful for filtering.

Running external commands.

type FoldCallback a = a -> Text -> a #

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

see run

run_ :: FilePath -> [Text] -> Sh () #

see run_

runFoldLines :: a -> FoldCallback a -> FilePath -> [Text] -> Sh a #

cmd :: ShellCommand result => FilePath -> result #

see cmd

(-|-) :: Sh Text -> Sh b -> Sh b #

see -|-

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

Modifying and querying environment.

setenv :: Text -> Text -> Sh () #

see setenv

get_env :: Text -> Sh (Maybe Text) #

get_env_text :: Text -> Sh Text #

get_env_def :: Text -> Text -> Sh Text #

Deprecated: use fromMaybe DEFAULT get_env

see get_env_def

Environment directory

cd :: FilePath -> Sh () #

see cd

chdir :: FilePath -> Sh a -> Sh a #

see chdir

Printing

echo :: Text -> Sh () #

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

echo_n :: Text -> Sh () #

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

echo_err :: Text -> Sh () #

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

echo_n_err :: Text -> Sh () #

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

inspect :: Show s => s -> Sh () #

inspect_err :: Show s => s -> Sh () #

tag :: Sh a -> Text -> Sh a #

see tag

trace :: Text -> Sh () #

see trace

show_command :: FilePath -> [Text] -> Text #

Querying filesystem.

lsT :: FilePath -> Sh Text #

see lsT

which :: FilePath -> Sh (Maybe FilePath) #

see 'S.which

Filename helpers

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

uses System.FilePath.CurrentOS, but can automatically convert a Text

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

uses System.FilePath.CurrentOS, but can automatically convert a Text

relativeTo #

Arguments

:: FilePath

anchor path, the prefix

-> FilePath

make this relative to anchor path

-> Sh FilePath 

hasExt :: Text -> FilePath -> Bool #

flipped hasExtension for Text

Manipulating filesystem.

mv :: FilePath -> FilePath -> Sh () #

see mv

rm :: FilePath -> Sh () #

see rm

rm_f :: FilePath -> Sh () #

see rm_f

rm_rf :: FilePath -> Sh () #

see rm_rf

cp :: FilePath -> FilePath -> Sh () #

see cp

cp_r :: FilePath -> FilePath -> Sh () #

see cp_r

mkdir :: FilePath -> Sh () #

see mkdir

reading/writing Files

readfile :: FilePath -> Sh Text #

writefile :: FilePath -> Text -> Sh () #

appendfile :: FilePath -> Text -> Sh () #

withTmpDir :: (FilePath -> Sh a) -> Sh a #

exiting the program

exit :: Int -> Sh () #

see exit

errorExit :: Text -> Sh () #

quietExit :: Int -> Sh () #

terror :: Text -> Sh a #

see terror

Exceptions

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

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

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

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

data ShellyHandler a #

Constructors

Exception e => ShellyHandler (e -> Sh a) 

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

convert between Text and FilePath

toTextIgnore :: FilePath -> Text #

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

fromText :: Text -> FilePath #

Utilities.

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

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 :: Sh a -> Sh (Double, a) #

see time

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 # 

Methods

toTextArg :: FilePath -> Text #

internal functions for writing extensions

get :: Sh State #

put :: State -> Sh () #

find functions

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

findDirFilterWhen #

Arguments

:: (FilePath -> Sh Bool)

directory filter

-> (FilePath -> Sh Bool)

file filter

-> FilePath

directory

-> Sh FilePath