shell-monad-0.2.1: shell monad

Safe HaskellNone
LanguageHaskell98

Control.Monad.Shell

Description

This is a shell monad, for generating shell scripts.

Synopsis

Documentation

data Script a Source

Shell script monad.

Instances

Monad Script 
Functor Script 
(~) * f () => CmdParams (Script f) 

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 
Param 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) 
Param (Quoted Text)

Quoted Text arguments are passed as-is.

quote :: Text -> Quoted Text Source

Quotes the Text 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.

glob :: Text -> Quoted Text Source

Treats the Text as a glob, which expands to one parameter per matching file.

The input is assumed to be a well-formed glob. Characters in it that are not alphanumeric and are not wildcard characters will be escaped before it is exposed to the shell. This allows eg, spaces in globs.

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

Adds a shell command to the script.

cmd :: (Param command, CmdParams params) => command -> params Source

Variadic and polymorphic version of run

A command can be passed any number of Params.

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

For the most efficient use of cmd, add the following boilerplate, which will make string literals in your program default to being Text:

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

Note that the command to run is itself a Param, so it can be a Text, or a String, or even a Var or Output. For example, this echos "hi":

demo = script $ do
   echovar <- newVarContaining "echo" ()
   cmd echovar "hi"

class Param a Source

A Param is anything that can be used as the parameter of a command.

Minimal complete definition

toTextParam

Instances

Param String

String arguments are automatically quoted.

Param Text

Text arguments are automatically quoted.

Param Output

Allows passing the output of a command as a parameter.

Param Var

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

Show v => Param (Val v)

Any value that can be shown can be passed to cmd; just wrap it inside a Val.

Param (Quoted Text)

Quoted Text arguments are passed as-is.

class CmdParams t Source

Allows a function to take any number of Params.

Minimal complete definition

cmdAll

Instances

(~) * f () => CmdParams (Script f) 
(Param arg, CmdParams result) => CmdParams (arg -> result) 

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

Param Output

Allows passing the output of a command as a parameter.

newtype Val v Source

An arbitrary value.

Constructors

Val v 

Instances

Show v => Param (Val v)

Any value that can be shown can be passed to cmd; just wrap it inside a Val.

comment :: Text -> Script () Source

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

newtype NamedLike Source

Suggests that a shell variable or function have its name contain the specified Text.

Constructors

NamedLike Text 

class NameHinted h Source

Class of values that provide a hint for the name to use for a shell variable or function.

To skip providing a hint, use '()'. To provide a hint, use '(NamedLike "name")'.

Minimal complete definition

hinted

newVar :: NameHinted namehint => namehint -> Script Var Source

Defines a new shell variable.

Each call to newVar will generate a new, unique variable name.

The namehint can influence this name, but is modified to ensure uniqueness.

newVarContaining :: NameHinted namehint => Text -> namehint -> Script Var Source

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

positionalParameters :: Var Source

This special Var expands to whatever parameters were passed to the shell script.

Inside a func, it expands to whatever parameters were passed to the func.

(This is $@ in shell)

takeParameter :: NameHinted namehint => namehint -> Script Var Source

Takes the first positional parameter, removing it from positionalParameters and returning a new Var that holds the value of the parameter.

If there are no more positional parameters, the script will crash with an error.

For example:

removefirstfile = script $ do
  cmd "rm" =<< takeParameter
  cmd "echo" "remaining parameters:" positionalParameters

func :: (NameHinted namehint, CmdParams callfunc) => namehint -> Script () -> Script callfunc Source

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

The action is variadic; it can be passed any number of CmdParams. Typically, it will make sense to specify a more concrete type when defining the shell function.

The shell function will be given a unique name, that is not used by any other shell function. The namehint can be used to influence the contents of the function name, which makes for more readable generated shell code.

For example:

demo = script $ do
   hohoho <- mkHohoho
   hohoho (Val 1)
   echo "And I heard him exclaim, ere he rode out of sight ..."
   hohoho (Val 3)

mkHohoho :: Script (Val Int -> Script ())
mkHohoho = func (NamedLike "hohoho") $ do
   num <- takeParameter
   forCmd (cmd "seq" "1" num) $ \_n ->
      cmd "echo" "Ho, ho, ho!" "Merry xmas!"

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.

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

Pipes together two Scripts.

(-&&-) :: Script () -> Script () -> Script () Source

ANDs two Scripts.

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

ORs two Scripts.

class RedirFile r Source

Any function that takes a RedirFile can be passed a a FilePath, in which case the default file descriptor will be redirected to/from the FilePath.

Or, it can be passed a tuple of (Fd, FilePath), in which case the specified Fd will be redirected to/from the FilePath.

Minimal complete definition

fromRedirFile

(|>) :: RedirFile f => Script () -> f -> Script () Source

Redirects to a file, overwriting any existing file.

For example, to shut up a noisy command:

cmd "find" "/" |> "/dev/null"

(|>>) :: RedirFile f => Script () -> f -> Script () Source

Appends to a file. (If file doesn't exist, it will be created.)

(|<) :: RedirFile f => Script () -> f -> Script () Source

Redirects standard input from a file.

toStderr :: Script () -> Script () Source

Redirects a script's output to stderr.

(|>&) :: (Script (), Fd) -> Fd -> Script () Source

Redirects the first file descriptor to output to the second.

For example, to redirect a command's stderr to stdout:

cmd "foo" ->- stdError) |>& stdOutput

(|<&) :: (Script (), Fd) -> Fd -> Script () Source

Redirects the first file descriptor to input from the second.

(->-) :: Script () -> Fd -> (Script (), Fd) Source

Helper for |>& and |<&

hereDocument :: Script () -> Text -> Script () Source

Provides the Text as input to the Script, using a here-document.