shell-monad-0.6.2: shell monad

Safe HaskellNone
LanguageHaskell98

Control.Monad.Shell

Contents

Description

This is a shell monad, for generating shell scripts.

Synopsis

Core

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 Term t a Source

A term that can be expanded in a shell command line.

Instances

(Show a, Num a) => Num (Term Static a) 
Show a => Param (Term Static a) 
Param (Term Var a) 

data Var Source

Used to represent a shell variable.

Instances

Param (Term Var a) 

data Static Source

Used for a static value.

Instances

(Show a, Num a) => Num (Term Static a) 
Show a => Param (Term Static a) 

data Quoted a Source

A value that is safely quoted so that it can be exposed to the shell.

While the constructor is exposed, you should avoid directly constucting Quoted values. Instead, use quote.

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.

class Quotable t where Source

Quotes a 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.

Methods

quote :: t -> Quoted Text Source

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.

Running commands

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 Arith

Allows passing an Arithmetic Expression as a parameter.

Param Output

Allows passing the output of a command as a parameter.

Param (Quoted Text)

Quoted Text arguments are passed as-is.

Param (WithVar a)

Allows modifying the value of a shell variable before it is passed to the command.

Show a => Param (Term Static a) 
Param (Term Var a) 

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.

Shell variables

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.

If you don't want to provide a naming hint, use ().

v1 <- newVar ()

To provide a naming hint, use either NamedLike.

v1 <- newVar (NamedLike "x")

Minimal complete definition

hinted

static :: Quotable (Val t) => t -> Term Static t Source

Makes a Static Term from any value that can be shown.

newVar :: NameHinted namehint => forall a. namehint -> Script (Term Var a) Source

Defines a new shell variable, which starts out not being set.

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, Quotable (Val t)) => t -> namehint -> Script (Term Var t) Source

Creates a new shell variable, with an initial value which can be anything that can be shown.

s <- newVarContaining "foo bar baz" (NamedLike "s")
i <- newVarContaining (1 :: Int) (NamedLike "i")

setVar :: Param param => forall a. Term Var a -> param -> Script () Source

Sets the Var to the value of the param.

globalVar :: forall a. Text -> Script (Term Var a) Source

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

positionalParameters :: forall a. Term Var a 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 => forall a. namehint -> Script (Term Var a) 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

defaultVar :: Param param => forall a. Term Var a -> param -> Script (Term Var a) Source

Generates a new Var. Expanding this Var will yield the same result as expanding the input Var, unless it is empty, in which case it instead defaults to the expansion of the param.

whenVar :: Param param => forall a. Term Var a -> param -> Script (Term Var a) Source

Generates a new Var. If the input Var is empty, then this new Var will likewise expand to the empty string. But if not, the new Var expands to the param.

lengthVar :: forall a. Term Var a -> Script (Term Var Integer) Source

Generates a new Var, which expands to the length of the expansion of the input Var.

Note that 'lengthVar positionalParameters' expands to the number of positional parameters.

trimVar :: forall a. Greediness -> Direction -> Term Var String -> Quoted Text -> Script (Term Var a) Source

Produces a Var that is a trimmed version of the input Var.

The Quoted Text is removed from the value of the Var, either from the beginning or from the end.

If the Quoted Text was produced by glob, it could match in multiple ways. You can choose whether to remove the shortest or the longest match.

The act of trimming a Var is assumed to be able to produce a new Var holding a different data type.

data WithVar a Source

Allows modifying the value of a variable before it is passed to a command. The function is passed a Quoted Text which will expand to the value of the variable, and can modify it, by using eg mappend.

cmd "rmdir" (WithVar name ("/home/" <>))

Constructors

WithVar (Term Var a) (Quoted Text -> Quoted Text) 

Instances

Param (WithVar a)

Allows modifying the value of a shell variable before it is passed to the command.

Monadic combinators

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 (static 1)
   echo "And I heard him exclaim, ere he rode out of sight ..."
   hohoho (static 3)

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

forCmd :: forall a. Script () -> (Term Var a -> 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 Script 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

caseOf :: forall a. Term Var a -> [(Quoted Text, Script ())] -> Script () Source

Matches the value of the Var against the Quoted Text (which can be generated by glob), and runs the Script action associated with the first match.

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

Pipes together two Scripts.

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

ANDs two Scripts.

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

ORs two Scripts.

Redirection

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.

For example, to read from Fd 42:

cmd "foo" &stdInput<&Fd 42

(&) :: 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.

Error handling

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.

errUnlessVar :: Param param => forall a. Term Var a -> param -> Script (Term Var a) Source

Generates a new Var. If the input Var is empty then expanding this new Var will cause an error to be thrown, using the param as the error message. If the input Var is not empty, then the new Var expands to the same thing the input Var expands to.

Tests

test :: Test -> Script () Source

Creates a Script that checks a Test and exits true (0) or false (1).

Useful with ifCmd, whenCmd, etc; for example:

ifCmd (test (FileExists "foo")) (foo, bar)

data Test where Source

Note that this should only include things that test(1) and shell built-in test commands support portably.

Constructors

TNot :: Test -> Test 
TAnd :: Test -> Test -> Test 
TOr :: Test -> Test -> Test 
TEmpty :: Param p => p -> Test 
TNonEmpty :: Param p => p -> Test 
TStrEqual :: (Param p, Param q) => p -> q -> Test 
TStrNotEqual :: (Param p, Param q) => p -> q -> Test 
TEqual :: (Integral p, Integral q) => Term Var p -> Term Var q -> Test 
TNotEqual :: (Integral p, Integral q) => Term Var p -> Term Var q -> Test 
TGT :: (Integral p, Integral q) => Term Var p -> Term Var q -> Test 
TLT :: (Integral p, Integral q) => Term Var p -> Term Var q -> Test 
TGE :: (Integral p, Integral q) => Term Var p -> Term Var q -> Test 
TLE :: (Integral p, Integral q) => Term Var p -> Term Var q -> Test 
TFileEqual :: (Param p, Param q) => p -> q -> Test 
TFileNewer :: (Param p, Param q) => p -> q -> Test 
TFileOlder :: (Param p, Param q) => p -> q -> Test 
TBlockExists :: Param p => p -> Test 
TCharExists :: Param p => p -> Test 
TDirExists :: Param p => p -> Test 
TFileExists :: Param p => p -> Test 
TRegularFileExists :: Param p => p -> Test 
TSymlinkExists :: Param p => p -> Test 
TFileNonEmpty :: Param p => p -> Test 
TFileExecutable :: Param p => p -> Test 

Shell Arithmetic Expressions

val :: Term t Integer -> Arith Source

Lifts a Term to Arith.

data Arith Source

This data type represents shell Arithmetic Expressions.

Note that in shell arithmetic, expressions that would evaluate to a Bool, such as ANot and AEqual instead evaluate to 1 for True and 0 for False.

Constructors

ANum Integer 
AVar (Term Var Integer) 
AStatic (Term Static Integer) 
ANegate Arith

negation

APlus Arith Arith

+

AMinus Arith Arith

-

AMult Arith Arith

*

ADiv Arith Arith

/

AMod Arith Arith

mod

ANot Arith

not

AOr Arith Arith

or

AAnd Arith Arith

and

AEqual Arith Arith

==

ANotEqual Arith Arith

/=

ALT Arith Arith

<

AGT Arith Arith

>

ALE Arith Arith

<=

AGE Arith Arith

>=

ABitOr Arith Arith

OR of the bits of the two arguments

ABitXOr Arith Arith

XOR of the bits of the two arguments

ABitAnd Arith Arith

AND of the bits of the two arguments

AShiftLeft Arith Arith

shift left (first argument's bits are shifted by the value of the second argument)

AShiftRight Arith Arith

shift right

AIf Arith (Arith, Arith)

if the first argument is non-zero, the result is the second, else the result is the third

Instances

Enum Arith

Note that fromEnum, enumFromTo, and enumFromThenTo cannot be used with Arith.

Num Arith

Arith is an instance of Num, which allows you to write expressions like this with shell variables, that generate Arithmetic Expressions.

val x * (100 + val y)
Param Arith

Allows passing an Arithmetic Expression as a parameter.

Misc

comment :: Text -> Script () Source

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

readVar :: Term Var String -> Script () Source

Fills a variable with a line read from stdin.