2014-03-31 03:37:54 +00:00
|
|
|
module Propellor.Property where
|
2014-03-30 03:10:52 +00:00
|
|
|
|
|
|
|
import System.Directory
|
|
|
|
import Control.Monad
|
2014-03-31 14:36:45 +00:00
|
|
|
import Data.Monoid
|
2014-03-30 03:10:52 +00:00
|
|
|
|
2014-03-31 03:37:54 +00:00
|
|
|
import Propellor.Types
|
2014-03-31 05:06:44 +00:00
|
|
|
import Propellor.Engine
|
2014-03-30 05:13:53 +00:00
|
|
|
import Utility.Monad
|
2014-03-30 03:10:52 +00:00
|
|
|
|
2014-03-30 19:31:57 +00:00
|
|
|
makeChange :: IO () -> IO Result
|
|
|
|
makeChange a = a >> return MadeChange
|
|
|
|
|
|
|
|
noChange :: IO Result
|
|
|
|
noChange = return NoChange
|
2014-03-30 03:10:52 +00:00
|
|
|
|
2014-03-31 14:36:45 +00:00
|
|
|
-- | Combines a list of properties, resulting in a single property
|
|
|
|
-- that when run will run each property in the list in turn,
|
|
|
|
-- and print out the description of each as it's run. Does not stop
|
|
|
|
-- on failure; does propigate overall success/failure.
|
2014-03-30 06:26:23 +00:00
|
|
|
propertyList :: Desc -> [Property] -> Property
|
2014-03-30 19:31:57 +00:00
|
|
|
propertyList desc ps = Property desc $ ensureProperties' ps
|
2014-03-30 06:26:23 +00:00
|
|
|
|
2014-03-31 14:36:45 +00:00
|
|
|
-- | Combines a list of properties, resulting in one property that
|
|
|
|
-- ensures each in turn, stopping on failure.
|
2014-04-01 21:32:37 +00:00
|
|
|
combineProperties :: Desc -> [Property] -> Property
|
|
|
|
combineProperties desc ps = Property desc $ go ps NoChange
|
2014-03-30 03:10:52 +00:00
|
|
|
where
|
|
|
|
go [] rs = return rs
|
|
|
|
go (l:ls) rs = do
|
|
|
|
r <- ensureProperty l
|
|
|
|
case r of
|
|
|
|
FailedChange -> return FailedChange
|
2014-03-31 14:36:45 +00:00
|
|
|
_ -> go ls (r <> rs)
|
2014-03-30 03:10:52 +00:00
|
|
|
|
2014-03-31 14:36:45 +00:00
|
|
|
-- | Makes a perhaps non-idempotent Property be idempotent by using a flag
|
|
|
|
-- file to indicate whether it has run before.
|
|
|
|
-- Use with caution.
|
2014-03-30 19:31:57 +00:00
|
|
|
flagFile :: Property -> FilePath -> Property
|
|
|
|
flagFile property flagfile = Property (propertyDesc property) $
|
|
|
|
go =<< doesFileExist flagfile
|
2014-03-30 03:10:52 +00:00
|
|
|
where
|
2014-03-30 19:31:57 +00:00
|
|
|
go True = return NoChange
|
|
|
|
go False = do
|
|
|
|
r <- ensureProperty property
|
|
|
|
when (r == MadeChange) $
|
|
|
|
writeFile flagfile ""
|
|
|
|
return r
|
|
|
|
|
2014-03-31 14:36:45 +00:00
|
|
|
--- | Whenever a change has to be made for a Property, causes a hook
|
|
|
|
-- Property to also be run, but not otherwise.
|
2014-03-30 19:31:57 +00:00
|
|
|
onChange :: Property -> Property -> Property
|
|
|
|
property `onChange` hook = Property (propertyDesc property) $ do
|
|
|
|
r <- ensureProperty property
|
|
|
|
case r of
|
|
|
|
MadeChange -> do
|
|
|
|
r' <- ensureProperty hook
|
2014-03-31 14:36:45 +00:00
|
|
|
return $ r <> r'
|
2014-03-30 19:31:57 +00:00
|
|
|
_ -> return r
|
|
|
|
|
2014-03-30 20:49:59 +00:00
|
|
|
(==>) :: Desc -> Property -> Property
|
|
|
|
(==>) = flip describe
|
|
|
|
infixl 1 ==>
|
|
|
|
|
2014-03-31 14:36:45 +00:00
|
|
|
-- | Makes a Property only be performed when a test succeeds.
|
2014-03-30 19:31:57 +00:00
|
|
|
check :: IO Bool -> Property -> Property
|
|
|
|
check c property = Property (propertyDesc property) $ ifM c
|
|
|
|
( ensureProperty property
|
|
|
|
, return NoChange
|
|
|
|
)
|
2014-04-02 16:13:39 +00:00
|
|
|
|
2014-04-03 00:56:02 +00:00
|
|
|
boolProperty :: Desc -> IO Bool -> Property
|
|
|
|
boolProperty desc a = Property desc $ ifM a
|
|
|
|
( return MadeChange
|
|
|
|
, return FailedChange
|
|
|
|
)
|
|
|
|
|
2014-04-02 16:13:39 +00:00
|
|
|
-- | Undoes the effect of a property.
|
|
|
|
revert :: RevertableProperty -> RevertableProperty
|
|
|
|
revert (RevertableProperty p1 p2) = RevertableProperty p2 p1
|
|
|
|
|
|
|
|
-- | Starts a list of Properties
|
|
|
|
props :: [Property]
|
|
|
|
props = []
|
|
|
|
|
|
|
|
-- | Adds a property to the list.
|
|
|
|
-- Can add both Properties and RevertableProperties.
|
|
|
|
(&) :: IsProp p => [Property] -> p -> [Property]
|
2014-04-02 17:20:39 +00:00
|
|
|
ps & p = ps ++ [toProp p]
|
2014-04-02 16:13:39 +00:00
|
|
|
infixl 1 &
|
2014-04-03 03:01:40 +00:00
|
|
|
|
|
|
|
-- | Adds a property to the list in reverted form.
|
|
|
|
(!) :: [Property] -> RevertableProperty -> [Property]
|
|
|
|
ps ! p = ps ++ [toProp $ revert p]
|
|
|
|
infixl 1 !
|