shelly-1.6.2.2: 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 Source

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

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

Performs shelly and then an empty action return ().

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

see shelly

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

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_

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

see cmd

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

see -|-

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

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

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

Modifying and querying environment.

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

see setenv

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

Querying filesystem.

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

see 'S.which

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

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

exiting the program

exit :: Int -> Sh () Source

see exit

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) 

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

Utilities.

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

An infix synonym for fmap.

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

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