propellor/Propellor/Property.hs

128 lines
3.7 KiB
Haskell
Raw Normal View History

{-# LANGUAGE PackageImports #-}
2014-03-31 03:37:54 +00:00
module Propellor.Property where
import System.Directory
import Control.Monad
2014-03-31 14:36:45 +00:00
import Data.Monoid
2014-04-10 15:02:29 +00:00
import Control.Monad.IfElse
import "mtl" Control.Monad.Reader
2014-03-31 03:37:54 +00:00
import Propellor.Types
2014-04-11 01:09:20 +00:00
import Propellor.Types.Attr
2014-03-31 05:06:44 +00:00
import Propellor.Engine
2014-03-30 05:13:53 +00:00
import Utility.Monad
2014-04-13 01:34:25 +00:00
import System.FilePath
makeChange :: IO () -> Propellor Result
makeChange a = liftIO a >> return MadeChange
2014-03-30 19:31:57 +00:00
noChange :: Propellor Result
2014-03-30 19:31:57 +00:00
noChange = return NoChange
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
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
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-04-08 22:41:30 +00:00
-- | Combines together two properties, resulting in one property
-- that ensures the first, and if the first succeeds, ensures the second.
-- The property uses the description of the first property.
before :: Property -> Property -> Property
p1 `before` p2 = Property (propertyDesc p1) $ do
r <- ensureProperty p1
case r of
FailedChange -> return FailedChange
_ -> ensureProperty p2
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
2014-04-13 01:34:25 +00:00
flagFile property = flagFile' property . return
flagFile' :: Property -> IO FilePath -> Property
flagFile' property getflagfile = Property (propertyDesc property) $ do
flagfile <- liftIO getflagfile
go flagfile =<< liftIO (doesFileExist flagfile)
where
2014-04-13 01:34:25 +00:00
go _ True = return NoChange
go flagfile False = do
2014-03-30 19:31:57 +00:00
r <- ensureProperty property
when (r == MadeChange) $ liftIO $
2014-04-13 01:34:25 +00:00
unlessM (doesFileExist flagfile) $ do
createDirectoryIfMissing True (takeDirectory flagfile)
2014-04-10 15:02:29 +00:00
writeFile flagfile ""
2014-03-30 19:31:57 +00:00
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 (liftIO c)
2014-03-30 19:31:57 +00:00
( 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 (liftIO a)
2014-04-03 00:56:02 +00:00
( 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
2014-04-11 01:09:20 +00:00
-- | Starts accumulating the properties of a Host.
--
-- > host "example.com"
-- > & someproperty
-- > ! oldproperty
-- > & otherproperty
host :: HostName -> Host
host hn = Host [] (\_ -> newAttr hn)
-- | Adds a property to a Host
2014-04-11 06:03:51 +00:00
--
2014-04-11 01:09:20 +00:00
-- Can add Properties, RevertableProperties, and AttrProperties
(&) :: IsProp p => Host -> p -> Host
2014-04-11 04:35:48 +00:00
(Host ps as) & p = Host (ps ++ [toProp p]) (getAttr p . as)
2014-04-02 16:13:39 +00:00
infixl 1 &
2014-04-03 03:01:40 +00:00
2014-04-11 01:09:20 +00:00
-- | Adds a property to the Host in reverted form.
(!) :: Host -> RevertableProperty -> Host
2014-04-11 04:35:48 +00:00
(Host ps as) ! p = Host (ps ++ [toProp q]) (getAttr q . as)
2014-04-11 01:09:20 +00:00
where
q = revert p
2014-04-03 03:01:40 +00:00
infixl 1 !