zifter-0.0.1.1: zifter

Safe HaskellNone
LanguageHaskell2010

Zifter.Zift

Synopsis

Documentation

getRootDir :: Zift (Path Abs Dir) Source #

Get the root directory of the zift.hs script that is being executed.

getSetting :: (Settings -> a) -> Zift a Source #

Get a single setting

ziftP :: [Zift ()] -> Zift () Source #

Declare a given list of Zift actions to be execute in parallel.

printZift :: String -> Zift () Source #

Print a message (with a newline appended to the end).

printZiftMessage :: String -> Zift () Source #

Print a message (with a newline appended to the end), in the standard zift script color. This is the function that the zift script uses to output information about the stages of the zift script run.

printPreprocessingDone :: String -> Zift () Source #

Print a message (with a newline appended to the end) that signifies that a part of the processing is now done.

Example:

doThingZift :: Zift ()
doThingZift = do
    doThing
    printProcessingDone "doThing completed successfully."

printPreprocessingError :: String -> Zift () Source #

Print a message (with a newline appended to the end) that signifies that a part of the processing failed. This message will not cause the zift script run to fail.

Example:

doDangerousThing :: Zift ()
doDangerousThing = do
    errOrResult <- doThing
    case errOrResult of
        Left err ->
            printPreprocessingError $
                unwords ["doThing failed with error:", err]
            fail "doThing failed."
        Right result -> do
            printPreprocessingDone
                unwords ["doThing succeeded with result:", result]

printWithColors :: [SGR] -> String -> Zift () Source #

Print a message (with a newline appended to the end) with custom colors.

See the ansi-terminal package for more details.

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.