propellor spin
This commit is contained in:
parent
2383674638
commit
9d348647d9
|
@ -5,7 +5,6 @@
|
||||||
--
|
--
|
||||||
-- A simple propellor program example:
|
-- A simple propellor program example:
|
||||||
--
|
--
|
||||||
--
|
|
||||||
-- > import Propellor
|
-- > import Propellor
|
||||||
-- > import Propellor.CmdLine
|
-- > import Propellor.CmdLine
|
||||||
-- > import qualified Propellor.Property.File as File
|
-- > import qualified Propellor.Property.File as File
|
||||||
|
@ -31,12 +30,14 @@ module Propellor (
|
||||||
, module Propellor.Property
|
, module Propellor.Property
|
||||||
, module Propellor.Property.Cmd
|
, module Propellor.Property.Cmd
|
||||||
, module Propellor.PrivData
|
, module Propellor.PrivData
|
||||||
|
, module Propellor.Engine
|
||||||
|
|
||||||
, module X
|
, module X
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Propellor.Types
|
import Propellor.Types
|
||||||
import Propellor.Property
|
import Propellor.Property
|
||||||
|
import Propellor.Engine
|
||||||
import Propellor.Property.Cmd
|
import Propellor.Property.Cmd
|
||||||
import Propellor.PrivData
|
import Propellor.PrivData
|
||||||
|
|
||||||
|
|
|
@ -0,0 +1,47 @@
|
||||||
|
module Propellor.Engine where
|
||||||
|
|
||||||
|
import System.Console.ANSI
|
||||||
|
import System.Exit
|
||||||
|
import System.IO
|
||||||
|
|
||||||
|
import Propellor.Types
|
||||||
|
import Utility.Exception
|
||||||
|
|
||||||
|
ensureProperty :: Property -> IO Result
|
||||||
|
ensureProperty = catchDefaultIO FailedChange . propertySatisfy
|
||||||
|
|
||||||
|
ensureProperties :: [Property] -> IO ()
|
||||||
|
ensureProperties ps = do
|
||||||
|
r <- ensureProperties' [Property "overall" $ ensureProperties' ps]
|
||||||
|
case r of
|
||||||
|
FailedChange -> exitWith (ExitFailure 1)
|
||||||
|
_ -> exitWith ExitSuccess
|
||||||
|
|
||||||
|
ensureProperties' :: [Property] -> IO Result
|
||||||
|
ensureProperties' ps = ensure ps NoChange
|
||||||
|
where
|
||||||
|
ensure [] rs = return rs
|
||||||
|
ensure (l:ls) rs = do
|
||||||
|
r <- ensureProperty l
|
||||||
|
clearFromCursorToLineBeginning
|
||||||
|
setCursorColumn 0
|
||||||
|
putStr $ propertyDesc l ++ "... "
|
||||||
|
case r of
|
||||||
|
FailedChange -> do
|
||||||
|
setSGR [SetColor Foreground Vivid Red]
|
||||||
|
putStrLn "failed"
|
||||||
|
NoChange -> do
|
||||||
|
setSGR [SetColor Foreground Dull Green]
|
||||||
|
putStrLn "unchanged"
|
||||||
|
MadeChange -> do
|
||||||
|
setSGR [SetColor Foreground Vivid Green]
|
||||||
|
putStrLn "done"
|
||||||
|
setSGR []
|
||||||
|
ensure ls (combineResult r rs)
|
||||||
|
|
||||||
|
warningMessage :: String -> IO ()
|
||||||
|
warningMessage s = do
|
||||||
|
setSGR [SetColor Foreground Vivid Red]
|
||||||
|
putStrLn $ "** warning: " ++ s
|
||||||
|
setSGR []
|
||||||
|
hFlush stdout
|
|
@ -9,7 +9,7 @@ import Data.Maybe
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
|
||||||
import Propellor.Types
|
import Propellor.Types
|
||||||
import Propellor.Property
|
import Propellor.Engine
|
||||||
import Utility.Monad
|
import Utility.Monad
|
||||||
import Utility.PartialPrelude
|
import Utility.PartialPrelude
|
||||||
import Utility.Exception
|
import Utility.Exception
|
||||||
|
|
|
@ -2,13 +2,10 @@ module Propellor.Property where
|
||||||
|
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import System.Console.ANSI
|
|
||||||
import System.Exit
|
|
||||||
import System.IO
|
|
||||||
|
|
||||||
import Propellor.Types
|
import Propellor.Types
|
||||||
|
import Propellor.Engine
|
||||||
import Utility.Monad
|
import Utility.Monad
|
||||||
import Utility.Exception
|
|
||||||
|
|
||||||
makeChange :: IO () -> IO Result
|
makeChange :: IO () -> IO Result
|
||||||
makeChange a = a >> return MadeChange
|
makeChange a = a >> return MadeChange
|
||||||
|
@ -82,42 +79,3 @@ check c property = Property (propertyDesc property) $ ifM c
|
||||||
( ensureProperty property
|
( ensureProperty property
|
||||||
, return NoChange
|
, return NoChange
|
||||||
)
|
)
|
||||||
|
|
||||||
ensureProperty :: Property -> IO Result
|
|
||||||
ensureProperty = catchDefaultIO FailedChange . propertySatisfy
|
|
||||||
|
|
||||||
ensureProperties :: [Property] -> IO ()
|
|
||||||
ensureProperties ps = do
|
|
||||||
r <- ensureProperties' [propertyList "overall" ps]
|
|
||||||
case r of
|
|
||||||
FailedChange -> exitWith (ExitFailure 1)
|
|
||||||
_ -> exitWith ExitSuccess
|
|
||||||
|
|
||||||
ensureProperties' :: [Property] -> IO Result
|
|
||||||
ensureProperties' ps = ensure ps NoChange
|
|
||||||
where
|
|
||||||
ensure [] rs = return rs
|
|
||||||
ensure (l:ls) rs = do
|
|
||||||
r <- ensureProperty l
|
|
||||||
clearFromCursorToLineBeginning
|
|
||||||
setCursorColumn 0
|
|
||||||
putStr $ propertyDesc l ++ "... "
|
|
||||||
case r of
|
|
||||||
FailedChange -> do
|
|
||||||
setSGR [SetColor Foreground Vivid Red]
|
|
||||||
putStrLn "failed"
|
|
||||||
NoChange -> do
|
|
||||||
setSGR [SetColor Foreground Dull Green]
|
|
||||||
putStrLn "unchanged"
|
|
||||||
MadeChange -> do
|
|
||||||
setSGR [SetColor Foreground Vivid Green]
|
|
||||||
putStrLn "done"
|
|
||||||
setSGR []
|
|
||||||
ensure ls (combineResult r rs)
|
|
||||||
|
|
||||||
warningMessage :: String -> IO ()
|
|
||||||
warningMessage s = do
|
|
||||||
setSGR [SetColor Foreground Vivid Red]
|
|
||||||
putStrLn $ "** warning: " ++ s
|
|
||||||
setSGR []
|
|
||||||
hFlush stdout
|
|
||||||
|
|
|
@ -1,5 +1,5 @@
|
||||||
Name: propellor
|
Name: propellor
|
||||||
Version: 0.1
|
Version: 0.1.1
|
||||||
Cabal-Version: >= 1.6
|
Cabal-Version: >= 1.6
|
||||||
License: GPL
|
License: GPL
|
||||||
Maintainer: Joey Hess <joey@kitenet.net>
|
Maintainer: Joey Hess <joey@kitenet.net>
|
||||||
|
@ -60,6 +60,7 @@ Library
|
||||||
Propellor.Property.User
|
Propellor.Property.User
|
||||||
Propellor.CmdLine
|
Propellor.CmdLine
|
||||||
Propellor.PrivData
|
Propellor.PrivData
|
||||||
|
Propellor.Engine
|
||||||
Propellor.Types
|
Propellor.Types
|
||||||
Other-Modules:
|
Other-Modules:
|
||||||
Utility.Applicative
|
Utility.Applicative
|
||||||
|
|
Loading…
Reference in New Issue