Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Defines the main Build
monad and common utils.
- module BuildBox.Build.Testable
- data BuildState = BuildState {}
- buildStateDefault :: FilePath -> BuildState
- type Build a = StateT BuildState IO a
- runBuild :: FilePath -> Build a -> IO (Either BuildError a)
- runBuildWithState :: BuildState -> Build a -> IO (Maybe a)
- runBuildPrint :: FilePath -> Build a -> IO (Maybe a)
- runBuildPrintWithState :: BuildState -> Build a -> IO (Maybe a)
- successfully :: IO a -> IO ()
- data BuildError
- = ErrorOther String
- | ErrorSystemCmdFailed { }
- | ErrorIOError IOError
- | Show prop => ErrorCheckFailed Bool prop
- | ErrorNeeds FilePath
- throw :: (MonadThrow m, Exception e) => e -> m a
- catch :: MonadCatch m => forall e a. Exception e => m a -> (e -> m a) -> m a
- needs :: FilePath -> Build ()
- io :: IO a -> Build a
- whenM :: Monad m => m Bool -> m () -> m ()
- out :: Text -> Build ()
- outLn :: Text -> Build ()
- outBlank :: Build ()
- outLine :: Build ()
- outLINE :: Build ()
- logSystem :: String -> Build ()
Documentation
module BuildBox.Build.Testable
data BuildState Source #
Global builder configuration.
BuildState | |
|
buildStateDefault :: FilePath -> BuildState Source #
The default build config.
type Build a = StateT BuildState IO a Source #
The builder monad encapsulates and IO action that can fail with an error, and also read some global configuration info.
Building
runBuild :: FilePath -> Build a -> IO (Either BuildError a) Source #
Run a build command. The first argument is a directory that can be used for temporary files (like "/tmp")
runBuildWithState :: BuildState -> Build a -> IO (Maybe a) Source #
Like runBuild
but also takes a BuildState
.
runBuildPrint :: FilePath -> Build a -> IO (Maybe a) Source #
Like runBuild
, but report whether it succeeded to the console.
If it succeeded then return Just the result, else Nothing.
runBuildPrintWithState :: BuildState -> Build a -> IO (Maybe a) Source #
Like runBuildPrint
but also takes a BuildState
.
successfully :: IO a -> IO () Source #
Discard the resulting value of a compuation.
Used like successfully . runBuild ...
Errors
data BuildError Source #
The errors we recognise.
ErrorOther String | Some generic error |
ErrorSystemCmdFailed | Some system command fell over, and it barfed out the given stdout and stderr. |
ErrorIOError IOError | Some miscellanous IO action failed. |
Show prop => ErrorCheckFailed Bool prop | Some property |
ErrorNeeds FilePath | A build command needs the following file to continue. This can be used for writing make-like bots. |
catch :: MonadCatch m => forall e a. Exception e => m a -> (e -> m a) -> m a #
Provide a handler for exceptions thrown during execution of the first
action. Note that type of the type of the argument to the handler will
constrain which exceptions are caught. See Control.Exception's
catch
.
needs :: FilePath -> Build () Source #
Throw a needs error saying we needs the given file. A catcher could then usefully create the file, or defer the compuation until it has been created.
Utils
io :: IO a -> Build a Source #
Lift an IO action into the build monad.
If the action throws any exceptions they get caught and turned into
ErrorIOError
exceptions in our Build
monad.