2014-04-10 21:22:32 +00:00
|
|
|
{-# LANGUAGE PackageImports #-}
|
|
|
|
|
2014-03-31 05:06:44 +00:00
|
|
|
module Propellor.Engine where
|
|
|
|
|
|
|
|
import System.Exit
|
|
|
|
import System.IO
|
2014-03-31 14:36:45 +00:00
|
|
|
import Data.Monoid
|
2014-03-31 22:31:08 +00:00
|
|
|
import System.Console.ANSI
|
2014-04-10 21:22:32 +00:00
|
|
|
import "mtl" Control.Monad.Reader
|
2014-03-31 05:06:44 +00:00
|
|
|
|
|
|
|
import Propellor.Types
|
2014-03-31 22:31:08 +00:00
|
|
|
import Propellor.Message
|
2014-04-10 21:22:32 +00:00
|
|
|
import Propellor.Exception
|
2014-03-31 05:06:44 +00:00
|
|
|
|
2014-04-11 01:09:20 +00:00
|
|
|
runPropellor :: Attr -> Propellor a -> IO a
|
|
|
|
runPropellor attr a = runReaderT (runWithAttr a) attr
|
2014-03-31 05:06:44 +00:00
|
|
|
|
2014-04-11 01:09:20 +00:00
|
|
|
mainProperties :: Attr -> [Property] -> IO ()
|
|
|
|
mainProperties attr ps = do
|
|
|
|
r <- runPropellor attr $
|
2014-04-18 08:48:49 +00:00
|
|
|
ensureProperties [Property "overall" (ensureProperties ps) id]
|
2014-03-31 23:31:35 +00:00
|
|
|
setTitle "propellor: done"
|
2014-03-31 05:19:40 +00:00
|
|
|
hFlush stdout
|
2014-03-31 05:06:44 +00:00
|
|
|
case r of
|
|
|
|
FailedChange -> exitWith (ExitFailure 1)
|
|
|
|
_ -> exitWith ExitSuccess
|
|
|
|
|
2014-04-10 21:22:32 +00:00
|
|
|
ensureProperties :: [Property] -> Propellor Result
|
|
|
|
ensureProperties ps = ensure ps NoChange
|
2014-03-31 05:06:44 +00:00
|
|
|
where
|
|
|
|
ensure [] rs = return rs
|
|
|
|
ensure (l:ls) rs = do
|
2014-03-31 22:31:08 +00:00
|
|
|
r <- actionMessage (propertyDesc l) (ensureProperty l)
|
2014-03-31 14:36:45 +00:00
|
|
|
ensure ls (r <> rs)
|
2014-04-10 21:22:32 +00:00
|
|
|
|
|
|
|
ensureProperty :: Property -> Propellor Result
|
|
|
|
ensureProperty = catchPropellor . propertySatisfy
|