| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Shelly.Pipe
Contents
- Entering Sh.
- List functions
- Running external commands.
- Modifying and querying environment.
- Environment directory
- Printing
- Querying filesystem.
- Filename helpers
- Manipulating filesystem.
- reading/writing Files
- exiting the program
- Exceptions
- convert between Text and FilePath
- Utilities.
- Re-exported for your convenience
- internal functions for writing extensions
- find functions
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)- data Sh a
- shs :: MonadIO m => Sh () -> m ()
- shelly :: MonadIO m => Sh a -> m [a]
- shellyFailDir :: MonadIO m => Sh a -> m [a]
- shsFailDir :: MonadIO m => Sh () -> m ()
- sub :: Sh a -> Sh a
- silently :: Sh a -> Sh a
- verbosely :: Sh a -> Sh a
- escaping :: Bool -> Sh a -> Sh a
- print_stdout :: Bool -> Sh a -> Sh a
- print_commands :: Bool -> Sh a -> Sh a
- 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
- roll :: Sh [a] -> Sh a
- unroll :: Sh a -> Sh [a]
- liftSh :: ([a] -> [b]) -> Sh a -> Sh b
- type FoldCallback a = a -> Text -> a
- run :: FilePath -> [Text] -> Sh Text
- run_ :: FilePath -> [Text] -> Sh ()
- runFoldLines :: a -> FoldCallback a -> FilePath -> [Text] -> Sh a
- cmd :: ShellCommand result => FilePath -> result
- (-|-) :: Sh Text -> Sh b -> Sh b
- lastStderr :: Sh Text
- setStdin :: Text -> Sh ()
- lastExitCode :: Sh Int
- 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 ()
- setenv :: Text -> Text -> Sh ()
- get_env :: Text -> Sh (Maybe Text)
- get_env_text :: Text -> Sh Text
- get_env_def :: Text -> Text -> Sh Text
- appendToPath :: FilePath -> Sh ()
- cd :: FilePath -> Sh ()
- chdir :: FilePath -> Sh a -> Sh a
- pwd :: Sh FilePath
- echo :: Text -> Sh ()
- echo_n :: Text -> Sh ()
- echo_err :: Text -> Sh ()
- echo_n_err :: Text -> Sh ()
- inspect :: Show s => s -> Sh ()
- inspect_err :: Show s => s -> Sh ()
- tag :: Sh a -> Text -> Sh a
- trace :: Text -> Sh ()
- show_command :: FilePath -> [Text] -> Text
- ls :: FilePath -> Sh FilePath
- lsT :: FilePath -> Sh Text
- test_e :: FilePath -> Sh Bool
- test_f :: FilePath -> Sh Bool
- test_d :: FilePath -> Sh Bool
- test_s :: FilePath -> Sh Bool
- which :: FilePath -> Sh (Maybe FilePath)
- absPath :: FilePath -> Sh FilePath
- (</>) :: (ToFilePath filepath1, ToFilePath filepath2) => filepath1 -> filepath2 -> FilePath
- (<.>) :: ToFilePath filepath => filepath -> Text -> FilePath
- canonic :: FilePath -> Sh FilePath
- canonicalize :: FilePath -> Sh FilePath
- relPath :: FilePath -> Sh FilePath
- relativeTo :: FilePath -> FilePath -> Sh FilePath
- hasExt :: Text -> FilePath -> Bool
- mv :: FilePath -> FilePath -> Sh ()
- rm :: FilePath -> Sh ()
- rm_f :: FilePath -> Sh ()
- rm_rf :: FilePath -> Sh ()
- cp :: FilePath -> FilePath -> Sh ()
- cp_r :: FilePath -> FilePath -> Sh ()
- mkdir :: FilePath -> Sh ()
- mkdir_p :: FilePath -> Sh ()
- mkdirTree :: Tree FilePath -> Sh ()
- readfile :: FilePath -> Sh Text
- readBinary :: FilePath -> Sh ByteString
- writefile :: FilePath -> Text -> Sh ()
- appendfile :: FilePath -> Text -> Sh ()
- touchfile :: FilePath -> Sh ()
- withTmpDir :: (FilePath -> Sh a) -> Sh a
- exit :: Int -> Sh ()
- errorExit :: Text -> Sh ()
- quietExit :: Int -> Sh ()
- terror :: Text -> Sh a
- catchany :: IO a -> (SomeException -> IO a) -> IO a
- catch_sh :: Exception e => Sh a -> (e -> Sh a) -> Sh a
- finally_sh :: Sh a -> Sh b -> Sh a
- data ShellyHandler a = forall e . Exception e => ShellyHandler (e -> Sh a)
- catches_sh :: Sh a -> [ShellyHandler a] -> Sh a
- catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh a
- toTextIgnore :: FilePath -> Text
- toTextWarn :: FilePath -> Sh Text
- fromText :: Text -> FilePath
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- whenM :: Monad m => m Bool -> m () -> m ()
- unlessM :: Monad m => m Bool -> m () -> m ()
- time :: Sh a -> Sh (Double, a)
- liftIO :: MonadIO m => forall a. IO a -> m a
- when :: Applicative f => Bool -> f () -> f ()
- unless :: Applicative f => Bool -> f () -> f ()
- data FilePath :: *
- get :: Sh State
- put :: State -> Sh ()
- find :: FilePath -> Sh FilePath
- findWhen :: (FilePath -> Sh Bool) -> FilePath -> Sh FilePath
- findFold :: (a -> FilePath -> Sh a) -> a -> FilePath -> Sh a
- findDirFilter :: (FilePath -> Sh Bool) -> FilePath -> Sh FilePath
- findDirFilterWhen :: (FilePath -> Sh Bool) -> (FilePath -> Sh Bool) -> FilePath -> Sh FilePath
- findFoldDirFilter :: (a -> FilePath -> Sh a) -> a -> (FilePath -> Sh Bool) -> FilePath -> Sh a
Entering Sh.
This type is a simple wrapper for a type Shelly.Sh.
 Sh contains a list of results. 
shellyFailDir :: MonadIO m => Sh a -> m [a] Source
see shellyFailDir
shsFailDir :: MonadIO m => Sh () -> m () Source
Performs shellyFailDir and then an empty action return ().
print_stdout :: Bool -> Sh a -> Sh a Source
see print_stdout
print_commands :: Bool -> Sh a -> Sh a Source
see 'S.print_commands
log_stdout_with :: (Text -> IO ()) -> Sh a -> Sh a Source
see log_stdout_with
log_stderr_with :: (Text -> IO ()) -> Sh a -> Sh a Source
see log_stderr_with
List functions
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
runFoldLines :: a -> FoldCallback a -> FilePath -> [Text] -> Sh a Source
see runFoldLines
lastStderr :: Sh Text Source
see lastStderr
lastExitCode :: Sh Int Source
see lastExitCode
Modifying and querying environment.
get_env_text :: Text -> Sh Text Source
see get_env_text
get_env_def :: Text -> Text -> Sh Text Source
Deprecated: use fromMaybe DEFAULT get_env
see get_env_def
appendToPath :: FilePath -> Sh () Source
see appendToPath
Environment directory
Printing
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_err :: Show s => s -> Sh () Source
see inspect_err
show_command :: FilePath -> [Text] -> Text Source
see show_command
Querying filesystem.
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
canonicalize :: FilePath -> Sh FilePath Source
see canonicalize
Arguments
| :: FilePath | anchor path, the prefix | 
| -> FilePath | make this relative to anchor path | 
| -> Sh FilePath | 
see relativeTo
Manipulating filesystem.
reading/writing Files
readBinary :: FilePath -> Sh ByteString Source
see readBinary
appendfile :: FilePath -> Text -> Sh () Source
see appendFile
withTmpDir :: (FilePath -> Sh a) -> Sh a Source
see withTmpDir
exiting the program
Exceptions
catchany :: IO a -> (SomeException -> IO a) -> IO a Source
A helper to catch any exception (same as
 ... ).catch (e :: SomeException) -> ...
finally_sh :: Sh a -> Sh b -> Sh a Source
see finally_sh
data ShellyHandler a Source
see ShellyHandler
Constructors
| forall e . Exception e => ShellyHandler (e -> Sh a) | 
catches_sh :: Sh a -> [ShellyHandler a] -> Sh a Source
see catches_sh
catchany_sh :: Sh a -> (SomeException -> Sh a) -> Sh a Source
see catchany_sh
convert between Text and FilePath
toTextIgnore :: FilePath -> Text Source
silently uses the Right or Left value of "Filesystem.Path.CurrentOS.toText"
toTextWarn :: FilePath -> Sh Text Source
see toTextWarn
Utilities.
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4
An infix synonym for fmap.
Examples
Convert from a Maybe IntMaybe Stringshow:
>>>show <$> NothingNothing>>>show <$> Just 3Just "3"
Convert from an Either Int IntEither IntString using show:
>>>show <$> Left 17Left 17>>>show <$> Right 17Right "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)
unlessM :: Monad m => m Bool -> m () -> m () Source
A monadic-conditional version of the unless guard.
Re-exported for your convenience
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 :: *
internal functions for writing extensions
find functions
findDirFilter :: (FilePath -> Sh Bool) -> FilePath -> Sh FilePath Source
see findDirFilter