shell-monad-0.0.2: shell monad

Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Monad.Shell

Description

A shell script monad

Synopsis

Documentation

data Script a Source

Shell script monad.

script :: Script f -> Text Source

Generates a shell script, including hashbang, suitable to be written to a file.

linearScript :: Script f -> Text Source

Generates a single line of shell code.

data Var Source

A shell variable.

Instances

val :: Var -> Q Source

Expand a shell variable to its value.

data Q Source

A piece of text that is safely quoted.

Instances

quote :: Text -> Q Source

Quotes the value to allow it to be safely exposed to the shell.

The method used is to replace ' with '"'"' and wrap the value inside single quotes. This works for POSIX shells, as well as other shells like csh.

data Expr Source

A shell expression.

indent :: Expr -> Expr Source

Indents an Expr

run :: Text -> [Text] -> Script () Source

Adds a shell command to the script.

cmd :: ShellCmd result => Text -> result Source

Variadic argument version of run.

The command can be passed any number of arguments. As well as passing Text and Q arguments, it also accepts Var arguments, which passes the value of a shell variable to the command.

Convenient usage of cmd requires the following:

{-# LANGUAGE OverloadedStrings, ExtendedDefaultRules #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
import Control.Monad.Shell
import qualified Data.Text.Lazy as L
default (L.Text)

This allows writing, for example:

demo = script $ do
  cmd "echo" "hello, world"
  name <- newVar "name"
  readVar name
  cmd "echo" "hello" name

add :: Expr -> Script () Source

Adds an Expr to the script.

comment :: Text -> Script () Source

Adds a comment that is embedded in the generated shell script.

newVar Source

Arguments

:: Text

base of variable name

-> Script Var 

Defines a new shell variable.

The name of the variable that appears in the shell script will be based on provided name, but each call to newVar will generate a new, unique variable name.

newVarContaining Source

Arguments

:: Text

base of variable name

-> Text

value

-> Script Var 

Creates a new shell variable, with an initial value.

globalVar :: Text -> Script Var Source

Gets a Var that refers to a global variable, such as PATH

func :: Script () -> Script (Script ()) Source

Defines a shell function, and returns an action that can be run to call the function.

TODO parameter passing to the function

(-|-) :: Script () -> Script () -> Script () Source

Pipes together two Scripts.

forCmd :: Script () -> (Var -> Script ()) -> Script () Source

Runs the command, and separates its output into parts (using the IFS)

The action is run for each part, passed a Var containing the part.

whileCmd :: Script () -> Script () -> Script () Source

As long as the first Script exits nonzero, runs the second script.

ifCmd :: Script () -> Script () -> Script () -> Script () Source

if with a monadic conditional

If the conditional exits 0, the first action is run, else the second.

whenCmd :: Script () -> Script () -> Script () Source

when with a monadic conditional

unlessCmd :: Script () -> Script () -> Script () Source

unless with a monadic conditional

readVar :: Var -> Script () Source

Generates shell code to read a variable from stdin.

stopOnFailure :: Bool -> Script () Source

By default, shell scripts continue running past commands that exit nonzero. Use "stopOnFailure True" to make the script stop on the first such command.

ignoreFailure :: Script () -> Script () Source

Makes a nonzero exit status be ignored.