Property tree

Properties now form a tree, instead of the flat list used before.

This simplifies propigation of Info from the Properties used inside a
container to the outer host; the Property that docks the container on the
host can just have as child properties all the inner Properties, and their
Info can then be gathered recursively. (Although in practice it still needs
to be filtered, since not all Info should propigate out of a container.)

Note that there is no change to how Properties are actually satisfied.
Just because a Property lists some child properties, this does not mean
they always have their propertySatisfy actions run. It's still up to the
parent property to run those actions.

That's necessary so that a container's properties can be satisfied inside
it, not outside. It also allows property combinators to
add the combined Properties to their childProperties list, even if,
like onChange, they don't always run the child properties at all.

Testing: I tested that the exact same Info is calculated before and after
this change, for every Host in my config file.
This commit is contained in:
Joey Hess 2015-01-18 18:02:07 -04:00
parent fcd8a3171b
commit afee550e70
10 changed files with 67 additions and 51 deletions

4
debian/changelog vendored
View File

@ -1,7 +1,9 @@
propellor (1.4.0) UNRELEASED; urgency=medium propellor (1.4.0) UNRELEASED; urgency=medium
* Add descriptions of how to set missing fields to --list-fields output. * Add descriptions of how to set missing fields to --list-fields output.
(Minor API changes) * Properties now form a tree, instead of the flat list used before.
This includes the properties used inside a container.
(API change)
-- Joey Hess <id@joeyh.name> Thu, 15 Jan 2015 20:14:29 -0400 -- Joey Hess <id@joeyh.name> Thu, 15 Jan 2015 20:14:29 -0400

View File

@ -35,7 +35,7 @@ import Utility.Monad
mainProperties :: Host -> IO () mainProperties :: Host -> IO ()
mainProperties host = do mainProperties host = do
ret <- runPropellor host $ ret <- runPropellor host $
ensureProperties [Property "overall" (ensureProperties $ hostProperties host) mempty] ensureProperties [Property "overall" (ensureProperties $ hostProperties host) mempty mempty]
h <- mkMessageHandle h <- mkMessageHandle
whenConsole h $ whenConsole h $
setTitle "propellor: done" setTitle "propellor: done"

View File

@ -3,12 +3,9 @@
module Propellor.Host where module Propellor.Host where
import Data.Monoid import Data.Monoid
import qualified Data.Set as S
import Propellor.Types import Propellor.Types
import Propellor.Info
import Propellor.Property import Propellor.Property
import Propellor.PrivData
-- | Starts accumulating the properties of a Host. -- | Starts accumulating the properties of a Host.
-- --
@ -35,8 +32,10 @@ class Hostlike h where
getHost :: h -> Host getHost :: h -> Host
instance Hostlike Host where instance Hostlike Host where
(Host hn ps is) & p = Host hn (ps ++ [toProp p]) (is <> getInfo p) (Host hn ps is) & p = Host hn (ps ++ [toProp p])
(Host hn ps is) &^ p = Host hn ([toProp p] ++ ps) (getInfo p <> is) (is <> getInfoRecursive p)
(Host hn ps is) &^ p = Host hn ([toProp p] ++ ps)
(getInfoRecursive p <> is)
getHost h = h getHost h = h
-- | Adds a property in reverted form. -- | Adds a property in reverted form.
@ -47,18 +46,29 @@ infixl 1 &^
infixl 1 & infixl 1 &
infixl 1 ! infixl 1 !
-- | When eg, docking a container, some of the Info about the container -- | Adjust the provided Property, adding to its
-- should propigate out to the Host it's on. This includes DNS info, -- propertyChidren the properties of the Hostlike.
-- so that eg, aliases of the container are reflected in the dns for the
-- host where it runs. -- The Info of the propertyChildren is adjusted to only include
-- info that should be propigated out to the Property.
-- --
-- This adjusts the Property that docks a container, to include such info -- DNS Info is propigated, so that eg, aliases of a Hostlike
-- from the container. -- are reflected in the dns for the host where it runs.
propigateInfo :: Hostlike hl => hl -> Property -> (Info -> Info) -> Property --
propigateInfo hl p f = combineProperties (propertyDesc p) $ -- PrivData Info is propigated, so that properties used inside a
p' : dnsprops ++ privprops -- Hostlike will have the necessary PrivData available.
propigateHostLike :: Hostlike hl => hl -> Property -> Property
propigateHostLike hl prop = prop
{ propertyChildren = propertyChildren prop ++ hostprops
}
where where
p' = p { propertyInfo = f (propertyInfo p) } hostprops = map go $ hostProperties $ getHost hl
i = hostInfo (getHost hl) go p =
dnsprops = map addDNS (S.toList $ _dns i) let i = propertyInfo p
privprops = map addPrivData (S.toList $ _privData i) in p
{ propertyInfo = mempty
{ _dns = _dns i
, _privData = _privData i
}
, propertyChildren = map go (propertyChildren p)
}

View File

@ -12,7 +12,7 @@ import Data.Monoid
import Control.Applicative import Control.Applicative
pureInfoProperty :: Desc -> Info -> Property pureInfoProperty :: Desc -> Info -> Property
pureInfoProperty desc = Property ("has " ++ desc) (return NoChange) pureInfoProperty desc i = Property ("has " ++ desc) (return NoChange) i mempty
askInfo :: (Info -> Val a) -> Propellor (Maybe a) askInfo :: (Info -> Val a) -> Propellor (Maybe a)
askInfo f = asks (fromVal . f . hostInfo) askInfo f = asks (fromVal . f . hostInfo)

View File

@ -16,19 +16,19 @@ import Utility.Monad
-- Constructs a Property. -- Constructs a Property.
property :: Desc -> Propellor Result -> Property property :: Desc -> Propellor Result -> Property
property d s = Property d s mempty property d s = Property d s mempty mempty
-- | Combines a list of properties, resulting in a single property -- | Combines a list of properties, resulting in a single property
-- that when run will run each property in the list in turn, -- 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 -- and print out the description of each as it's run. Does not stop
-- on failure; does propigate overall success/failure. -- on failure; does propigate overall success/failure.
propertyList :: Desc -> [Property] -> Property propertyList :: Desc -> [Property] -> Property
propertyList desc ps = Property desc (ensureProperties ps) (combineInfos ps) propertyList desc ps = Property desc (ensureProperties ps) mempty ps
-- | Combines a list of properties, resulting in one property that -- | Combines a list of properties, resulting in one property that
-- ensures each in turn. Stops if a property fails. -- ensures each in turn. Stops if a property fails.
combineProperties :: Desc -> [Property] -> Property combineProperties :: Desc -> [Property] -> Property
combineProperties desc ps = Property desc (go ps NoChange) (combineInfos ps) combineProperties desc ps = Property desc (go ps NoChange) mempty ps
where where
go [] rs = return rs go [] rs = return rs
go (l:ls) rs = do go (l:ls) rs = do
@ -67,15 +67,16 @@ flagFile' p getflagfile = adjustProperty p $ \satisfy -> do
--- | Whenever a change has to be made for a Property, causes a hook --- | Whenever a change has to be made for a Property, causes a hook
-- Property to also be run, but not otherwise. -- Property to also be run, but not otherwise.
onChange :: Property -> Property -> Property onChange :: Property -> Property -> Property
p `onChange` hook = Property (propertyDesc p) satisfy (combineInfo p hook) p `onChange` hook = p
where { propertySatisfy = do
satisfy = do
r <- ensureProperty p r <- ensureProperty p
case r of case r of
MadeChange -> do MadeChange -> do
r' <- ensureProperty hook r' <- ensureProperty hook
return $ r <> r' return $ r <> r'
_ -> return r _ -> return r
, propertyChildren = propertyChildren p ++ [hook]
}
(==>) :: Desc -> Property -> Property (==>) :: Desc -> Property -> Property
(==>) = flip describe (==>) = flip describe
@ -128,13 +129,6 @@ revert (RevertableProperty p1 p2) = RevertableProperty p2 p1
adjustProperty :: Property -> (Propellor Result -> Propellor Result) -> Property adjustProperty :: Property -> (Propellor Result -> Propellor Result) -> Property
adjustProperty p f = p { propertySatisfy = f (propertySatisfy p) } adjustProperty p f = p { propertySatisfy = f (propertySatisfy p) }
-- | Combines the Info of two properties.
combineInfo :: (IsProp p, IsProp q) => p -> q -> Info
combineInfo p q = getInfo p <> getInfo q
combineInfos :: IsProp p => [p] -> Info
combineInfos = mconcat . map getInfo
makeChange :: IO () -> Propellor Result makeChange :: IO () -> Propellor Result
makeChange a = liftIO a >> return MadeChange makeChange a = liftIO a >> return MadeChange

View File

@ -76,7 +76,9 @@ provisioned' propigator c@(Chroot loc system builderconf _) systemdonly = Revert
teardown = toProp (revert built) teardown = toProp (revert built)
propigateChrootInfo :: Chroot -> Property -> Property propigateChrootInfo :: Chroot -> Property -> Property
propigateChrootInfo c p = propigateInfo c p (<> chrootInfo c) propigateChrootInfo c p = propigateHostLike c p'
where
p' = p { propertyInfo = propertyInfo p <> chrootInfo c }
chrootInfo :: Chroot -> Info chrootInfo :: Chroot -> Info
chrootInfo (Chroot loc _ _ h) = chrootInfo (Chroot loc _ _ h) =

View File

@ -78,7 +78,7 @@ setupPrimary zonefile mknamedconffile hosts domain soa rs =
(partialzone, zonewarnings) = genZone indomain hostmap domain soa (partialzone, zonewarnings) = genZone indomain hostmap domain soa
baseprop = Property ("dns primary for " ++ domain) satisfy baseprop = Property ("dns primary for " ++ domain) satisfy
(addNamedConf conf) (addNamedConf conf) []
satisfy = do satisfy = do
sshfps <- concat <$> mapM (genSSHFP domain) (M.elems hostmap) sshfps <- concat <$> mapM (genSSHFP domain) (M.elems hostmap)
let zone = partialzone let zone = partialzone

View File

@ -134,9 +134,9 @@ docked ctr@(Container _ h) = RevertableProperty
] ]
propigateContainerInfo :: Container -> Property -> Property propigateContainerInfo :: Container -> Property -> Property
propigateContainerInfo ctr@(Container _ h) p = propigateContainerInfo ctr@(Container _ h) p = propigateHostLike ctr p'
propigateInfo ctr p (<> dockerinfo)
where where
p' = p { propertyInfo = propertyInfo p <> dockerinfo }
dockerinfo = dockerInfo $ dockerinfo = dockerInfo $
mempty { _dockerContainers = M.singleton (hostName h) h } mempty { _dockerContainers = M.singleton (hostName h) h }

View File

@ -419,7 +419,6 @@ kiteMailServer = propertyList "kitenet.net mail server"
, "/etc/default/spamassassin" `File.containsLines` , "/etc/default/spamassassin" `File.containsLines`
[ "# Propellor deployed" [ "# Propellor deployed"
, "ENABLED=1" , "ENABLED=1"
, "CRON=1"
, "OPTIONS=\"--create-prefs --max-children 5 --helper-home-dir\"" , "OPTIONS=\"--create-prefs --max-children 5 --helper-home-dir\""
, "CRON=1" , "CRON=1"
, "NICE=\"--nicelevel 15\"" , "NICE=\"--nicelevel 15\""

View File

@ -4,7 +4,7 @@
module Propellor.Types module Propellor.Types
( Host(..) ( Host(..)
, Info(..) , Info(..)
, getInfo , getInfoRecursive
, Propellor(..) , Propellor(..)
, Property(..) , Property(..)
, RevertableProperty(..) , RevertableProperty(..)
@ -38,7 +38,6 @@ import "mtl" Control.Monad.RWS.Strict
import "MonadCatchIO-transformers" Control.Monad.CatchIO import "MonadCatchIO-transformers" Control.Monad.CatchIO
import qualified Data.Set as S import qualified Data.Set as S
import qualified Data.Map as M import qualified Data.Map as M
import qualified Propellor.Types.Dns as Dns
import Propellor.Types.OS import Propellor.Types.OS
import Propellor.Types.Chroot import Propellor.Types.Chroot
@ -46,9 +45,10 @@ import Propellor.Types.Dns
import Propellor.Types.Docker import Propellor.Types.Docker
import Propellor.Types.PrivData import Propellor.Types.PrivData
import Propellor.Types.Empty import Propellor.Types.Empty
import qualified Propellor.Types.Dns as Dns
-- | Everything Propellor knows about a system: Its hostname, -- | Everything Propellor knows about a system: Its hostname,
-- properties and other info. -- properties and their collected info.
data Host = Host data Host = Host
{ hostName :: HostName { hostName :: HostName
, hostProperties :: [Property] , hostProperties :: [Property]
@ -77,7 +77,15 @@ data Property = Property
, propertySatisfy :: Propellor Result , propertySatisfy :: Propellor Result
-- ^ must be idempotent; may run repeatedly -- ^ must be idempotent; may run repeatedly
, propertyInfo :: Info , propertyInfo :: Info
-- ^ a property can add info to the host. -- ^ info associated with the property
, propertyChildren :: [Property]
-- ^ A property can include a list of child properties.
-- This allows them to be introspected to collect their info,
-- etc.
--
-- Note that listing Properties here does not ensure that
-- their propertySatisfy is run when satisfying the parent
-- property; it's up to the parent's propertySatisfy to do that.
} }
instance Show Property where instance Show Property where
@ -93,21 +101,22 @@ class IsProp p where
-- | Indicates that the first property can only be satisfied -- | Indicates that the first property can only be satisfied
-- once the second one is. -- once the second one is.
requires :: p -> Property -> p requires :: p -> Property -> p
getInfo :: p -> Info -- | Gets the info of the property, combined with all info
-- of all children properties.
getInfoRecursive :: p -> Info
instance IsProp Property where instance IsProp Property where
describe p d = p { propertyDesc = d } describe p d = p { propertyDesc = d }
toProp p = p toProp p = p
getInfo = propertyInfo getInfoRecursive p = propertyInfo p <> mconcat (map getInfoRecursive (propertyChildren p))
x `requires` y = Property (propertyDesc x) satisfy info x `requires` y = x
where { propertySatisfy = do
info = getInfo y <> getInfo x
satisfy = do
r <- propertySatisfy y r <- propertySatisfy y
case r of case r of
FailedChange -> return FailedChange FailedChange -> return FailedChange
_ -> propertySatisfy x _ -> propertySatisfy x
, propertyChildren = y : propertyChildren x
}
instance IsProp RevertableProperty where instance IsProp RevertableProperty where
-- | Sets the description of both sides. -- | Sets the description of both sides.
@ -117,7 +126,7 @@ instance IsProp RevertableProperty where
(RevertableProperty p1 p2) `requires` y = (RevertableProperty p1 p2) `requires` y =
RevertableProperty (p1 `requires` y) p2 RevertableProperty (p1 `requires` y) p2
-- | Return the Info of the currently active side. -- | Return the Info of the currently active side.
getInfo (RevertableProperty p1 _p2) = getInfo p1 getInfoRecursive (RevertableProperty p1 _p2) = getInfoRecursive p1
type Desc = String type Desc = String