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

Safe HaskellNone
LanguageHaskell98

Shelly

Contents

Description

A module for shell-like programming in Haskell. Shelly's focus is entirely on ease of use for those coming from shell scripting. However, it also tries to use modern libraries and techniques to keep things efficient.

The functionality provided by this module is (unlike standard Haskell filesystem functionality) thread-safe: each Sh maintains its own environment and its own working directory.

Recommended usage includes putting the following at the top of your program, otherwise you will likely need either type annotations or type conversions

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

Entering Sh.

data Sh a Source #

Instances
Monad Sh Source # 
Instance details

Defined in Shelly.Base

Methods

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

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

return :: a -> Sh a #

fail :: String -> Sh a #

Functor Sh Source # 
Instance details

Defined in Shelly.Base

Methods

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

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

MonadFail Sh Source # 
Instance details

Defined in Shelly.Base

Methods

fail :: String -> Sh a #

Applicative Sh Source # 
Instance details

Defined in Shelly.Base

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 #

MonadIO Sh Source # 
Instance details

Defined in Shelly.Base

Methods

liftIO :: IO a -> Sh a #

MonadThrow Sh Source # 
Instance details

Defined in Shelly.Base

Methods

throwM :: Exception e => e -> Sh a #

MonadCatch Sh Source # 
Instance details

Defined in Shelly.Base

Methods

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

MonadMask Sh Source # 
Instance details

Defined in Shelly.Base

Methods

mask :: ((forall a. Sh a -> Sh a) -> Sh b) -> Sh b #

uninterruptibleMask :: ((forall a. Sh a -> Sh a) -> Sh b) -> Sh b #

generalBracket :: Sh a -> (a -> ExitCase b -> Sh c) -> (a -> Sh b) -> Sh (b, c) #

MonadShControl Sh Source # 
Instance details

Defined in Shelly.Lifted

Associated Types

data ShM Sh a :: Type Source #

Methods

liftShWith :: ((forall x. Sh x -> Sh (ShM Sh x)) -> Sh a) -> Sh a Source #

restoreSh :: ShM Sh a -> Sh a Source #

MonadSh Sh Source # 
Instance details

Defined in Shelly.Lifted

Methods

liftSh :: Sh a -> Sh a Source #

MonadBase IO Sh Source # 
Instance details

Defined in Shelly.Base

Methods

liftBase :: IO α -> Sh α #

MonadBaseControl IO Sh Source # 
Instance details

Defined in Shelly.Base

Associated Types

type StM Sh a :: Type #

Methods

liftBaseWith :: (RunInBase Sh IO -> IO a) -> Sh a #

restoreM :: StM Sh a -> Sh a #

ShellCmd (Sh ()) Source # 
Instance details

Defined in Shelly

Methods

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

(s ~ Text, Show s) => ShellCmd (Sh s) Source # 
Instance details

Defined in Shelly

Methods

cmdAll :: FilePath -> [Text] -> Sh s Source #

ShellCmd (Sh Text) Source # 
Instance details

Defined in Shelly

Methods

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

newtype ShM Sh a Source # 
Instance details

Defined in Shelly.Lifted

newtype ShM Sh a = ShSh a
type StM Sh a Source # 
Instance details

Defined in Shelly.Base

type StM Sh a

type ShIO a = Sh a Source #

Deprecated: Use Sh instead of ShIO

ShIO is Deprecated in favor of Sh, which is easier to type.

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

Enter a Sh from (Monad)IO. The environment and working directories are inherited from the current process-wide values. Any subsequent changes in processwide working directory or environment are not reflected in the running Sh.

shellyNoDir :: MonadIO m => Sh a -> m a Source #

Deprecated: Just use shelly. The default settings have changed

Deprecated now, just use shelly, whose default has been changed. Using this entry point does not create a .shelly directory in the case of failure. Instead it logs directly into the standard error stream (stderr).

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

Using this entry point creates a .shelly directory in the case of failure where errors are recorded.

asyncSh :: Sh a -> Sh (Async a) Source #

spawn an asynchronous action with a copy of the current state

sub :: Sh a -> Sh a Source #

Enter a sub-Sh that inherits the environment The original state will be restored when the sub-Sh completes. Exceptions are propagated normally.

silently :: Sh a -> Sh a Source #

Create a sub-Sh in which external command outputs are not echoed and commands are not printed. See sub.

verbosely :: Sh a -> Sh a Source #

Create a sub-Sh in which external command outputs are echoed and Executed commands are printed See sub.

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

Create a sub-Sh with shell character escaping on or off. Defaults to True.

Setting to False allows for shell wildcard such as * to be expanded by the shell along with any other special shell characters. As a side-effect, setting to False causes changes to PATH to be ignored: see the run documentation.

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

Create a sub-Sh with stdout printing on or off Defaults to True.

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

Create a sub-Sh with stderr printing on or off Defaults to True.

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

Create a sub-Sh with command echoing on or off Defaults to False, set to True by verbosely

onCommandHandles :: StdInit -> Sh a -> Sh a Source #

When running an external command, apply the given initializers to the specified handles for that command. This can for example be used to change the encoding of the handles or set them into binary mode.

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

Create a sub-Sh where commands are not traced Defaults to True. You should only set to False temporarily for very specific reasons

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

named after bash -e errexit. Defaults to True. When True, throw an exception on a non-zero exit code. When False, ignore a non-zero exit code. Not recommended to set to False unless you are specifically checking the error code with lastExitCode.

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

Create a sub-Sh in which stdout is sent to the user-defined logger. When running with silently the given log will not be called for any output. Likewise the log will also not be called for output from run_ and bash_ commands.

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

Create a sub-Sh in which stderr is sent to the user-defined logger. When running with silently the given log will not be called for any output. However, unlike log_stdout_with the log will be called for output from run_ and bash_ commands.

Running external commands.

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

Execute an external command. Takes the command name and arguments.

You may prefer using cmd instead, which is a variadic argument version of this function.

stdout and stderr are collected. The stdout is returned as a result of run, and complete stderr output is available after the fact using lastStderr

All of the stdout output will be loaded into memory. You can avoid this if you don't need stdout by using run_, If you want to avoid the memory and need to process the output then use runFoldLines or runHandle or runHandles.

By default shell characters are escaped and the command name is a name of a program that can be found via PATH. Shelly will look through the PATH itself to find the command.

When escaping is set to False, shell characters are allowed. Since there is no longer a guarantee that a single program name is given, Shelly cannot look in the PATH for it. a PATH modified by setenv is not taken into account when finding the exe name. Instead the original Haskell program PATH is used. On a Posix system the env command can be used to make the setenv PATH used when escaping is set to False. env echo hello instead of echo hello

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

the same as run, but return () instead of the stdout content stdout will be read and discarded line-by-line

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

used by run. fold over stdout line-by-line as it is read to avoid keeping it in memory stderr is still being placed in memory under the assumption it is always relatively small

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

variadic argument version of run. Please see the documenation for run.

The syntax is more convenient, but more importantly it also allows the use of a FilePath as a command argument. So an argument can be a Text or a FilePath without manual conversions. a FilePath is automatically converted to Text with toTextIgnore.

Convenient usage of cmd requires the following:

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

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

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

Like run, but it invokes the user-requested program with _bash_.

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

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

Use this with bash to set _pipefail_

bashPipeFail $ bash "echo foo | echo"

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

Pipe operator. set the stdout the first command as the stdin of the second. This does not create a shell-level pipe, but hopefully it will in the future. To create a shell level pipe you can set escaping False and use a pipe | character in a command.

lastStderr :: Sh Text Source #

The output of last external command. See run.

setStdin :: Text -> Sh () Source #

set the stdin to be used and cleared by the next run.

lastExitCode :: Sh Int Source #

The exit code from the last command. Unless you set errExit to False you won't get a chance to use this: a non-zero exit code will throw an exception.

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

bind some arguments to run for re-use. Example:

monit = command "monit" ["-c", "monitrc"]
monit ["stop", "program"]

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

bind some arguments to run_ for re-use. Example:

monit_ = command_ "monit" ["-c", "monitrc"]
monit_ ["stop", "program"]

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

bind some arguments to run for re-use, and require 1 argument. Example:

git = command1 "git" []
git "pull" ["origin", "master"]

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

bind some arguments to run_ for re-use, and require 1 argument. Example:

git_ = command1_ "git" []
git "pull" ["origin", "master"]

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

run commands over SSH. An ssh executable is expected in your path. Commands are in the same form as run, but given as pairs

sshPairs "server-name" [("cd", "dir"), ("rm",["-r","dir2"])]

This interface is crude, but it works for now.

Please note this sets escaping to False, and the remote commands are quoted with single quotes, in a way such that the remote commands will see the literal values you passed, this means that no variable expansion and alike will done on either the local shell or the remote shell, and that if there are a single or double quotes in your arguments, they need not to be quoted manually.

Internally the list of commands are combined with the string && before given to ssh.

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

Same as sshPairs, but combines commands with the string &, so they will be started in parallell.

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

same as sshPairs, but returns ()

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

same as sshPairsP, but returns ()

sshPairsWithOptions Source #

Arguments

:: Text

Server name.

-> [Text]

Arguments to ssh (e.g. ["-p","22"]).

-> [(FilePath, [Text])]

Pairs of commands to run on the remote.

-> Sh Text

Returns the standard output.

Like sshPairs, but allows for arguments to the call to ssh.

data SshMode Source #

Constructors

ParSsh 
SeqSsh 

class ShellCmd t where Source #

For the variadic function cmd

partially applied variadic functions require type signatures

Methods

cmdAll :: FilePath -> [Text] -> t Source #

Instances
MonadSh m => ShellCmd (m ()) Source # 
Instance details

Defined in Shelly.Lifted

Methods

cmdAll :: FilePath -> [Text] -> m () Source #

(MonadSh m, s ~ Text, Show s) => ShellCmd (m s) Source # 
Instance details

Defined in Shelly.Lifted

Methods

cmdAll :: FilePath -> [Text] -> m s Source #

MonadSh m => ShellCmd (m Text) Source # 
Instance details

Defined in Shelly.Lifted

Methods

cmdAll :: FilePath -> [Text] -> m Text Source #

ShellCmd (Sh ()) Source # 
Instance details

Defined in Shelly

Methods

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

(s ~ Text, Show s) => ShellCmd (Sh s) Source # 
Instance details

Defined in Shelly

Methods

cmdAll :: FilePath -> [Text] -> Sh s Source #

ShellCmd (Sh Text) Source # 
Instance details

Defined in Shelly

Methods

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

(CmdArg arg, ShellCmd result) => ShellCmd ([arg] -> result) Source # 
Instance details

Defined in Shelly

Methods

cmdAll :: FilePath -> [Text] -> [arg] -> result Source #

(CmdArg arg, ShellCmd result) => ShellCmd (arg -> result) Source # 
Instance details

Defined in Shelly

Methods

cmdAll :: FilePath -> [Text] -> arg -> result Source #

class CmdArg a where Source #

Argument converter for the variadic argument version of run called cmd. Useful for a type signature of a function that uses cmd

Methods

toTextArg :: a -> Text Source #

Instances
CmdArg String Source # 
Instance details

Defined in Shelly

CmdArg Text Source # 
Instance details

Defined in Shelly

Methods

toTextArg :: Text -> Text Source #

Running commands Using handles

runHandle Source #

Arguments

:: FilePath

command

-> [Text]

arguments

-> (Handle -> Sh a)

stdout handle

-> Sh a 

Similar to run but gives the raw stdout handle in a callback. If you want even more control, use runHandles.

runHandles Source #

Arguments

:: FilePath

command

-> [Text]

arguments

-> [StdHandle]

optionally connect process i/o handles to existing handles

-> (Handle -> Handle -> Handle -> Sh a)

stdin, stdout and stderr

-> Sh a 

Similar to run but gives direct access to all input and output handles.

Be careful when using the optional input handles. If you specify Inherit for a handle then attempting to access the handle in your callback is an error

transferLinesAndCombine :: Handle -> (Text -> IO ()) -> IO Text Source #

Transfer from one handle to another For example, send contents of a process output to stdout. does not close the write handle.

Also, return the complete contents being streamed line by line.

transferFoldHandleLines :: a -> FoldCallback a -> Handle -> (Text -> IO ()) -> IO a Source #

Transfer from one handle to another For example, send contents of a process output to stdout. does not close the write handle.

Also, fold over the contents being streamed line by line

data StdStream #

Constructors

Inherit

Inherit Handle from parent

UseHandle Handle

Use the supplied Handle

CreatePipe

Create a new pipe. The returned Handle will use the default encoding and newline translation mode (just like Handles created by openFile).

NoStream

No stream handle will be passed

Instances
Eq StdStream 
Instance details

Defined in System.Process.Common

Show StdStream 
Instance details

Defined in System.Process.Common

Handle manipulation

type HandleInitializer = Handle -> IO () Source #

Initialize a handle before using it

data StdInit Source #

A collection of initializers for the three standard process handles

initOutputHandles :: HandleInitializer -> StdInit Source #

Apply a single initializer to the two output process handles (stdout and stderr)

initAllHandles :: HandleInitializer -> StdInit Source #

Apply a single initializer to all three standard process handles (stdin, stdout and stderr)

Modifying and querying environment.

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

Set an environment variable. The environment is maintained in Sh internally, and is passed to any external commands to be executed.

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

Fetch the current value of an environment variable. if non-existant or empty text, will be Nothing

get_env_text :: Text -> Sh Text Source #

Fetch the current value of an environment variable. Both empty and non-existent variables give empty string as a result.

getenv :: Text -> Sh Text Source #

Deprecated: use get_env or get_env_text

deprecated

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

Deprecated: use fromMaybe DEFAULT get_env

Fetch the current value of an environment variable. Both empty and non-existent variables give the default Text value as a result

get_env_all :: Sh [(String, String)] Source #

get the full environment

get_environment :: Sh [(String, String)] Source #

Deprecated: use get_env_all

appendToPath :: FilePath -> Sh () Source #

add the filepath onto the PATH env variable

prependToPath :: FilePath -> Sh () Source #

prepend the filepath to the PATH env variable similar to appendToPath but gives high priority to the filepath instead of low priority.

Environment directory

cd :: FilePath -> Sh () Source #

Change current working directory of Sh. This does *not* change the working directory of the process we are running it. Instead, Sh keeps track of its own working directory and builds absolute paths internally instead of passing down relative paths.

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

cd, execute a Sh action in the new directory and then pop back to the original directory

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

chdir, but first create the directory if it does not exit

pwd :: Sh FilePath Source #

Obtain the current (Sh) working directory.

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 #

a print lifted into Sh

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

a print lifted into Sh using stderr

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

same as trace, but use it combinator style

trace :: Text -> Sh () Source #

internally log what occurred. Log will be re-played on failure.

Querying filesystem.

ls :: FilePath -> Sh [FilePath] Source #

List directory contents. Does *not* include "." and "..", but it does include (other) hidden files.

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

Get back [Text] instead of [FilePath]

test_e :: FilePath -> Sh Bool Source #

Does a path point to an existing filesystem object?

test_f :: FilePath -> Sh Bool Source #

Does a path point to an existing file?

test_d :: FilePath -> Sh Bool Source #

Does a path point to an existing directory?

test_s :: FilePath -> Sh Bool Source #

Does a path point to a symlink?

test_px :: FilePath -> Sh Bool Source #

Test that a file is in the PATH and also executable

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

Get a full path to an executable by looking at the PATH environement variable. Windows normally looks in additional places besides the PATH: this does not duplicate that behavior.

Filename helpers

absPath :: FilePath -> Sh FilePath Source #

Make a relative path absolute by combining with the working directory. An absolute path is returned as is. To create a relative path, use relPath.

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

canonic :: FilePath -> Sh FilePath Source #

makes an absolute path. Like canonicalize, but on an exception returns absPath

canonicalize :: FilePath -> Sh FilePath Source #

Obtain a (reasonably) canonic file path to a filesystem object. Based on "canonicalizePath" in system-fileio.

relPath :: FilePath -> Sh FilePath Source #

Makes a relative path relative to the current Sh working directory. An absolute path is returned as is. To create an absolute path, use absPath

relativeTo Source #

Arguments

:: FilePath

anchor path, the prefix

-> FilePath

make this relative to anchor path

-> Sh FilePath 

make the second path relative to the first Uses stripPrefix, but will canonicalize the paths if necessary

path :: FilePath -> Sh FilePath Source #

Deprecated: use absPath, canonic, or relPath instead

deprecated

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

flipped hasExtension for Text

Manipulating filesystem.

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

Move a file. The second path could be a directory, in which case the original file is moved into that directory. wraps directory renameFile, which may not work across FS boundaries

rm :: FilePath -> Sh () Source #

Remove a file. Does fail if the file does not exist (use rm_f instead) or is not a file.

rm_f :: FilePath -> Sh () Source #

Remove a file. Does not fail if the file does not exist. Does fail if the file is not a file.

rm_rf :: FilePath -> Sh () Source #

A swiss army cannon for removing things. Actually this goes farther than a normal rm -rf, as it will circumvent permission problems for the files we own. Use carefully. Uses removeDirectoryRecursive

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

Copy a file. The second path could be a directory, in which case the original file name is used, in that directory.

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

Copy a file, or a directory recursively. uses cp

mkdir :: FilePath -> Sh () Source #

Create a new directory (fails if the directory exists).

mkdir_p :: FilePath -> Sh () Source #

Create a new directory, including parents (succeeds if the directory already exists).

mkdirTree :: Tree FilePath -> Sh () Source #

Create a new directory tree. You can describe a bunch of directories as a tree and this function will create all subdirectories. An example:

exec = mkTree $
          "package" # [
               "src" # [
                   "Data" # leaves ["Tree", "List", "Set", "Map"]
               ],
               "test" # leaves ["QuickCheck", "HUnit"],
               "dist/doc/html" # []
           ]
        where (#) = Node
              leaves = map (# [])

reading/writing Files

readBinary :: FilePath -> Sh ByteString Source #

wraps ByteSting readFile

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

Write a Text to a file.

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

Append a Text to a file.

touchfile :: FilePath -> Sh () Source #

Update a file, creating (a blank file) if it does not exist.

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

Create a temporary directory and pass it as a parameter to a Sh computation. The directory is nuked afterwards.

exiting the program

exit :: Int -> Sh a Source #

exit 0 means no errors, all other codes are error conditions

errorExit :: Text -> Sh a Source #

echo a message and exit with status 1

quietExit :: Int -> Sh a Source #

for exiting with status > 0 without printing debug information

terror :: Text -> Sh a Source #

fail that takes a Text

Exceptions

bracket_sh :: Sh a -> (a -> Sh b) -> (a -> Sh c) -> Sh c Source #

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 #

Same as a normal catch but specialized for the Sh monad.

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

Same as a normal handle but specialized for the Sh monad.

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

Handle any exception in the Sh monad.

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

Same as a normal finally but specialized for the Sh monad.

data ShellyHandler a Source #

You need to wrap exception handlers with this when using catches_sh.

Constructors

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

catches_sh :: Sh a -> [ShellyHandler a] -> Sh a Source #

Same as a normal catches, but specialized for the Sh monad.

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

Catch any exception in the Sh monad.

data ReThrownException e Source #

Shelly's wrapper around exceptions thrown in its monad

Constructors

ReThrownException e String 

convert between Text and FilePath

toTextIgnore :: FilePath -> Text Source #

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

fromText :: Text -> FilePath Source #

Convert Text to a FilePath-

Utility Functions

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 #

Run a Sh computation and collect timing information. The value returned is the amount of _real_ time spent running the computation in seconds, as measured by the system clock. The precision is determined by the resolution of getCurrentTime.

sleep :: Int -> Sh () Source #

threadDelay wrapper that uses seconds

Re-exported for your convenience

liftIO :: MonadIO m => 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.

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.

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

internal functions for writing extensions

get :: Sh State Source #

put :: State -> Sh () Source #

find functions

find :: FilePath -> Sh [FilePath] Source #

List directory recursively (like the POSIX utility "find"). listing is relative if the path given is relative. If you want to filter out some results or fold over them you can do that with the returned files. A more efficient approach is to use one of the other find functions.

findWhen :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath] Source #

find that filters the found files as it finds. Files must satisfy the given filter to be returned in the result.

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

Fold an arbitrary folding function over files froma a find. Like findWhen but use a more general fold rather than a filter.

findDirFilter :: (FilePath -> Sh Bool) -> FilePath -> Sh [FilePath] Source #

find that filters out directories as it finds Filtering out directories can make a find much more efficient by avoiding entire trees of files.

findDirFilterWhen Source #

Arguments

:: (FilePath -> Sh Bool)

directory filter

-> (FilePath -> Sh Bool)

file filter

-> FilePath

directory

-> Sh [FilePath] 

similar findWhen, but also filter out directories Alternatively, similar to findDirFilter, but also filter out files Filtering out directories makes the find much more efficient

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

like findDirFilterWhen but use a folding function rather than a filter The most general finder: you likely want a more specific one

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

find-command follows symbolic links. Defaults to False. When True, follow symbolic links. When False, never follow symbolic links.