| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
BuildEnv.Script
Description
This modules provides a tiny build script DSL.
A BuildScript is a series of simple build steps (process calls).
A BuildScript can be executed in the IO monad, using executeBuildScript.
A BuildScript can be turned into a shell script which can be executed
 later, using script.
Synopsis
- executeBuildScript :: SymbolicPath CWD (Dir Project) -> Maybe Counter -> BuildScript -> IO ()
 - script :: ScriptConfig -> BuildScript -> Text
 - type BuildScript = BuildScriptM ()
 - newtype BuildScriptM a = BuildScript {}
 - emptyBuildScript :: BuildScript
 - askScriptConfig :: BuildScriptM ScriptConfig
 - buildSteps :: ScriptConfig -> BuildScript -> BuildSteps
 - data BuildStep
- = forall dir. CallProcess (CallProcess dir)
 - | forall dir. CreateDir (AbsolutePath (Dir dir))
 - | LogMessage String
 - | ReportProgress { }
 
 - type BuildSteps = [BuildStep]
 - step :: BuildStep -> BuildScript
 - callProcess :: CallProcess dir -> BuildScript
 - createDir :: AbsolutePath (Dir dir) -> BuildScript
 - logMessage :: Verbosity -> Verbosity -> String -> BuildScript
 - reportProgress :: Verbosity -> BuildScript
 - data ScriptOutput
- = Run
 - | Shell { 
- useVariables :: !Bool
 
 
 - data ScriptConfig = ScriptConfig {
- scriptOutput :: !ScriptOutput
 - scriptWorkingDir :: !(SymbolicPath CWD (Dir Project))
 - scriptStyle :: !Style
 - scriptTotal :: !(Maybe Word)
 
 - hostRunCfg :: SymbolicPath CWD (Dir Project) -> Maybe Word -> ScriptConfig
 - data EscapeVars
 - quoteArg :: (IsString r, Monoid r) => EscapeVars -> ScriptConfig -> String -> r
 
Interpreting build scripts
Executing build scripts
Arguments
| :: SymbolicPath CWD (Dir Project) | Working directory.  | 
| -> Maybe Counter | Optional counter to use to report progress.  | 
| -> BuildScript | The build script to execute.  | 
| -> IO () | 
Execute a BuildScript in the IO monad.
Shell-script output
script :: ScriptConfig -> BuildScript -> Text Source #
Obtain the textual contents of a build script.
Build scripts
type BuildScript = BuildScriptM () Source #
A build script: a list of build steps, given a ScriptConfig context.
newtype BuildScriptM a Source #
Build script monad.
Constructors
| BuildScript | |
Fields  | |
Instances
emptyBuildScript :: BuildScript Source #
The empty build script: no build steps.
askScriptConfig :: BuildScriptM ScriptConfig Source #
Retrieve the ScriptConfig from the ReaderT environment.
buildSteps :: ScriptConfig -> BuildScript -> BuildSteps Source #
Obtain the build steps of a BuildScript.
Individual build steps
A build step.
Constructors
| forall dir. CallProcess (CallProcess dir) | Call a processs with the given arguments.  | 
| forall dir. CreateDir (AbsolutePath (Dir dir)) | Create the given directory.  | 
| LogMessage String | Log a message to   | 
| ReportProgress | Report one unit of progress.  | 
Fields 
  | |
type BuildSteps = [BuildStep] Source #
A list of build steps.
step :: BuildStep -> BuildScript Source #
Declare a build step.
callProcess :: CallProcess dir -> BuildScript Source #
Call a process with given arguments.
createDir :: AbsolutePath (Dir dir) -> BuildScript Source #
Create the given directory.
logMessage :: Verbosity -> Verbosity -> String -> BuildScript Source #
Log a message.
reportProgress :: Verbosity -> BuildScript Source #
Report one unit of progress.
Configuring build scripts
data ScriptOutput Source #
How to interpret the build script: run it in IO, or turn it
 into a shell script?
Constructors
| Run | Run the build script in   | 
| Shell | Generate a shell script.  | 
Fields 
  | |
data ScriptConfig Source #
Configuration options for a BuildScript.
Constructors
| ScriptConfig | |
Fields 
  | |
Arguments
| :: SymbolicPath CWD (Dir Project) | |
| -> Maybe Word | Optional: total to report progress against.  | 
| -> ScriptConfig | 
Configure a script to run on the host (in IO).
data EscapeVars Source #
Whether to expand or escape variables in a shell script.
Constructors
| ExpandVars | Allow the shell to expand variables.  | 
| EscapeVars | Escape variables so that the shell doesn't expand them.  | 
Instances
| Show EscapeVars Source # | |
Defined in BuildEnv.Script Methods showsPrec :: Int -> EscapeVars -> ShowS # show :: EscapeVars -> String # showList :: [EscapeVars] -> ShowS #  | |
quoteArg :: (IsString r, Monoid r) => EscapeVars -> ScriptConfig -> String -> r Source #
Quote a command-line argument, if the ScriptConfig requires arguments
 to be quoted.
No need to call this on the cwd or prog fields of BuildStep,
 as these will be quoted by the shell-script backend no matter what.