| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell98 |
Control.Monad.Shell
Description
A shell script monad
- data Script a
- script :: Script f -> Text
- linearScript :: Script f -> Text
- data Var
- val :: Var -> Q
- data Expr
- indent :: Expr -> Expr
- run :: Text -> [Text] -> Script ()
- cmd :: ShellCmd result => Text -> result
- add :: Expr -> Script ()
- comment :: Text -> Script ()
- newVar :: Text -> Script Var
- newVarContaining :: Text -> Text -> Script Var
- globalVar :: Text -> Script Var
- func :: Script () -> Script (Script ())
- forCmd :: Script () -> (Var -> Script ()) -> Script ()
- quote :: Text -> Q
- readVar :: Var -> Script ()
- (-|-) :: Script () -> Script () -> Script ()
Documentation
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.
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 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 T
default (L.Text)This allows writing, for example:
demo = script $ do cmd "echo" "hello, world" name <- newVar "name" readVar name cmd "echo" "hello" name
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.
Creates a new shell variable, with an initial value.
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
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.
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.