Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Versioned properties and hosts.
When importing and using this module, you will need to enable some language extensions:
{-# LANGUAGE RankNTypes, FlexibleContexts, TypeFamilies #-}
This module takes advantage of RevertableProperty
to let propellor
switch cleanly between versions. The way it works is all revertable
properties for other versions than the current version are first
reverted, and then propellor ensures the property for the current
version. This method should work for any combination of revertable
properties.
For example:
demo :: Versioned Int (RevertableProperty DebianLike DebianLike) demo ver = ver ( (== 1) --> Apache.modEnabled "foo" `requires` Apache.modEnabled "foosupport" <|> (== 2) --> Apache.modEnabled "bar" <|> (> 2) --> Apache.modEnabled "baz" ) foo :: Host foo = host "foo.example.com" $ props & demo `version` (2 :: Int)
Similarly, a whole Host can be versioned. For example:
bar :: Versioned Int Host bar ver = host "bar.example.com" $ props & osDebian Unstable X86_64 & ver ( (== 1) --> Apache.modEnabled "foo" <|> (== 2) --> Apache.modEnabled "bar" ) & ver ( (>= 2) --> Apt.unattendedUpgrades )
Note that some versioning of revertable properties may cause propellor to do a lot of unnecessary work each time it's run. Here's an example of such a problem:
slow :: Versioned Int -> RevertableProperty DebianLike DebianLike slow ver = ver ( (== 1) --> (Apt.installed "foo" <!> Apt.removed "foo") <|> (== 2) --> (Apt.installed "bar" <!> Apt.removed "bar") )
Suppose that package bar depends on package foo. Then at version 2, propellor will remove package foo in order to revert version 1, only to re-install it since version 2 also needs it installed.
Documentation
(-->) :: (v -> Bool) -> RevertableProperty metatypes metatypes -> VerSpec v metatypes infixl 8 Source #
Specify a function that checks the version, and what
RevertableProperty
to use if the version matches.