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

Shelly.Pipe

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"

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

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

Instances

Instances details
MonadIO Sh Source # 
Instance details

Defined in Shelly.Pipe

Methods

liftIO :: IO a -> Sh a #

Alternative Sh Source # 
Instance details

Defined in Shelly.Pipe

Methods

empty :: Sh a

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

some :: Sh a -> Sh [a]

many :: Sh a -> Sh [a]

Applicative Sh Source # 
Instance details

Defined in Shelly.Pipe

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 Source # 
Instance details

Defined in Shelly.Pipe

Methods

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

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

Monad Sh Source # 
Instance details

Defined in Shelly.Pipe

Methods

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

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

return :: a -> Sh a

MonadPlus Sh Source # 
Instance details

Defined in Shelly.Pipe

Methods

mzero :: Sh a

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

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

Performs shelly and then an empty action return ().

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

see shelly

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

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

Performs shellyFailDir and then an empty action return ().

sub :: Sh a -> Sh a Source #

see sub

silently :: Sh a -> Sh a Source #

verbosely :: Sh a -> Sh a Source #

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

print_stdout :: Bool -> Sh a -> Sh a Source #

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

see 'S.print_commands

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

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

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

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

List functions

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

Pack list of results. It performs concat inside Sh.

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

Unpack list of results.

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

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

Running external commands

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

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

see run

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

see run_

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

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

see cmd

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

see -|-

setStdin :: Text -> Sh () Source #

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

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

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

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

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

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

Modifying and querying environment

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

see setenv

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

get_env_text :: Text -> Sh Text Source #

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

Deprecated: use fromMaybe DEFAULT get_env

see get_env_def

Environment directory

cd :: FilePath -> Sh () Source #

see cd

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

see chdir

Printing

echo :: Text -> Sh () Source #

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

echo_n :: Text -> Sh () Source #

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

echo_err :: Text -> Sh () Source #

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

echo_n_err :: Text -> Sh () Source #

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

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

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

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

see tag

trace :: Text -> Sh () Source #

see trace

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

Querying filesystem

lsT :: FilePath -> Sh Text Source #

see lsT

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

see 'S.which

Filename helpers

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

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

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

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

relativeTo Source #

Arguments

:: FilePath

anchor path, the prefix

-> FilePath

make this relative to anchor path

-> Sh FilePath 

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

Flipped hasExtension for Text.

Manipulating filesystem

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

see mv

rm :: FilePath -> Sh () Source #

see rm

rm_f :: FilePath -> Sh () Source #

see rm_f

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

see cp

reading/writing Files

readBinary :: FilePath -> Sh ByteString Source #

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

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

exiting the program

exit :: Int -> Sh () Source #

see exit

errorExit :: Text -> Sh () Source #

quietExit :: Int -> Sh () Source #

terror :: Text -> Sh a Source #

see terror

Exceptions

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

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

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

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

data ShellyHandler a Source #

Constructors

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

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

convert between Text and FilePath

fromText :: Text -> FilePath Source #

Convert Text to a FilePath.

Utilities

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

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

see time

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 #

internal functions for writing extensions

get :: Sh State Source #

put :: State -> Sh () Source #

find functions

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

findDirFilterWhen Source #

Arguments

:: (FilePath -> Sh Bool)

directory filter

-> (FilePath -> Sh Bool)

file filter

-> FilePath

directory

-> Sh FilePath 

findFoldDirFilter :: (a -> FilePath -> Sh a) -> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a Source #

followSymlink :: Bool -> Sh a -> Sh a Source #