shell-monad-0.0.3: shell monad

Safe HaskellNone
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

Eq Var 
Ord Var 
Show Var 
CmdArg Var

Var arguments cause the (quoted) value of a shell variable to be passed to the command.

val :: Var -> Quoted Text Source

Expand a shell variable to its value.

data Quoted a Source

A value that is safely quoted.

Instances

Eq a => Eq (Quoted a) 
Ord a => Ord (Quoted a) 
Show a => Show (Quoted a) 
Monoid a => Monoid (Quoted a) 
CmdArg (Quoted Text)

Quoted Text arguments are passed as-is.

quote :: Text -> Quoted Text 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.

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

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

class CmdArg a Source

Minimal complete definition

toTextArg

Instances

CmdArg Text

Text arguments are automatically quoted.

CmdArg Output 
CmdArg Var

Var arguments cause the (quoted) value of a shell variable to be passed to the command.

CmdArg (Quoted Text)

Quoted Text arguments are passed as-is.

newtype Output Source

The output of a command, or even a more complicated Script can be passed as a parameter to cmd

Examples:

cmd "echo" "hello there," (Output (cmd "whoami"))
cmd "echo" "root's pwent" (Output (cmd "cat" "/etc/passwd" -|- cmd "grep" "root"))

Constructors

Output (Script ()) 

Instances

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 (which can be mempty), 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 fill a variable with a line read 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.