shelly-1.10.0: 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

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

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

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

Expand

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

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

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.

type FilePath = String #

File and directory names are values of type String, whose precise meaning is operating system dependent. Files can be opened, yielding a handle which can then be used to operate on the contents of that file.

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