propellor-5.3.4: property-based host configuration management in haskell

Safe HaskellNone
LanguageHaskell98

Propellor.Property

Contents

Synopsis

Property combinators

requires :: Combines x y => x -> y -> CombinedType x y Source #

Indicates that the first property depends on the second, so before the first is ensured, the second must be ensured.

The combined property uses the description of the first property.

before :: Combines x y => x -> y -> CombinedType x y Source #

Combines together two properties, resulting in one property that ensures the first, and if the first succeeds, ensures the second.

The combined property uses the description of the first property.

onChange :: Combines x y => x -> y -> CombinedType x y Source #

Whenever a change has to be made for a Property, causes a hook Property to also be run, but not otherwise.

onChangeFlagOnFail :: Combines x y => FilePath -> x -> y -> CombinedType x y Source #

Same as onChange except that if property y fails, a flag file is generated. On next run, if the flag file is present, property y is executed even if property x doesn't change.

With onChange, if y fails, the property x onChange y returns FailedChange. But if this property is applied again, it returns NoChange. This behavior can cause trouble...

flagFile :: Property i -> FilePath -> Property i Source #

Makes a perhaps non-idempotent Property be idempotent by using a flag file to indicate whether it has run before. Use with caution.

check :: (Checkable p i, LiftPropellor m) => m Bool -> p i -> Property i Source #

Makes a Property or an UncheckedProperty only run when a test succeeds.

fallback :: Combines p1 p2 => p1 -> p2 -> CombinedType p1 p2 Source #

Tries the first property, but if it fails to work, instead uses the second.

revert :: RevertableProperty setup undo -> RevertableProperty undo setup Source #

Undoes the effect of a RevertableProperty.

Property descriptions

describe :: IsProp p => p -> Desc -> p Source #

Changes the description of a property.

(==>) :: IsProp (Property i) => Desc -> Property i -> Property i infixl 1 Source #

Alias for flip describe

Constructing properties

data Propellor p Source #

Propellor's monad provides read-only access to info about the host it's running on, and a writer to accumulate EndActions.

Instances

Monad Propellor Source # 

Methods

(>>=) :: Propellor a -> (a -> Propellor b) -> Propellor b #

(>>) :: Propellor a -> Propellor b -> Propellor b #

return :: a -> Propellor a #

fail :: String -> Propellor a #

Functor Propellor Source # 

Methods

fmap :: (a -> b) -> Propellor a -> Propellor b #

(<$) :: a -> Propellor b -> Propellor a #

Applicative Propellor Source # 

Methods

pure :: a -> Propellor a #

(<*>) :: Propellor (a -> b) -> Propellor a -> Propellor b #

liftA2 :: (a -> b -> c) -> Propellor a -> Propellor b -> Propellor c #

(*>) :: Propellor a -> Propellor b -> Propellor b #

(<*) :: Propellor a -> Propellor b -> Propellor a #

MonadIO Propellor Source # 

Methods

liftIO :: IO a -> Propellor a #

MonadThrow Propellor Source # 

Methods

throwM :: Exception e => e -> Propellor a #

MonadCatch Propellor Source # 

Methods

catch :: Exception e => Propellor a -> (e -> Propellor a) -> Propellor a #

MonadMask Propellor Source # 

Methods

mask :: ((forall a. Propellor a -> Propellor a) -> Propellor b) -> Propellor b #

uninterruptibleMask :: ((forall a. Propellor a -> Propellor a) -> Propellor b) -> Propellor b #

generalBracket :: Propellor a -> (a -> ExitCase b -> Propellor c) -> (a -> Propellor b) -> Propellor (b, c) #

LiftPropellor Propellor Source # 
MonadReader Host Propellor Source # 

Methods

ask :: Propellor Host #

local :: (Host -> Host) -> Propellor a -> Propellor a #

reader :: (Host -> a) -> Propellor a #

Monoid (Propellor Result) Source #

When two actions are appended together, the second action is only run if the first action does not fail.

MonadWriter [EndAction] Propellor Source # 

Methods

writer :: (a, [EndAction]) -> Propellor a #

tell :: [EndAction] -> Propellor () #

listen :: Propellor a -> Propellor (a, [EndAction]) #

pass :: Propellor (a, [EndAction] -> [EndAction]) -> Propellor a #

property :: SingI metatypes => Desc -> Propellor Result -> Property (MetaTypes metatypes) Source #

Constructs a Property, from a description and an action to run to ensure the Property is met.

Due to the polymorphic return type of this function, most uses will need to specify a type signature. This lets you specify what OS the property targets, etc.

For example:

 foo :: Property Debian
 foo = property "foo" $ do
	...
 	return MadeChange

property' :: SingI metatypes => Desc -> (OuterMetaTypesWitness metatypes -> Propellor Result) -> Property (MetaTypes metatypes) Source #

Constructs a property, like property, but provides its OuterMetaTypesWitness.

data OuterMetaTypesWitness metatypes Source #

Used to provide the metatypes of a Property to calls to ensureProperty within it.

ensureProperty :: (Cannot_ensureProperty_WithInfo inner ~ True, (Targets inner `NotSuperset` Targets outer) ~ CanCombine) => OuterMetaTypesWitness outer -> Property (MetaTypes inner) -> Propellor Result Source #

For when code running in the Propellor monad needs to ensure a Property.

Use property' to get the OuterMetaTypesWithness. For example:

foo = Property Debian
foo = property' "my property" $ \w -> do
	ensureProperty w (aptInstall "foo")

The type checker will prevent using ensureProperty with a property that does not support the target OSes needed by the OuterMetaTypesWitness. In the example above, aptInstall must support Debian, since foo is supposed to support Debian.

The type checker will also prevent using ensureProperty with a property with HasInfo in its MetaTypes. Doing so would cause the Info associated with the property to be lost.

pickOS :: HasCallStack => (SingKind (KProxy :: KProxy ka), SingKind (KProxy :: KProxy kb), DemoteRep (KProxy :: KProxy ka) ~ [MetaType], DemoteRep (KProxy :: KProxy kb) ~ [MetaType], SingI c) => Property (MetaTypes (a :: ka)) -> Property (MetaTypes (b :: kb)) -> Property (MetaTypes c) Source #

Picks one of the two input properties to use, depending on the targeted OS.

If both input properties support the targeted OS, then the first will be used.

The resulting property will use the description of the first property no matter which property is used in the end. So, it's often a good idea to change the description to something clearer.

For example:

upgraded :: Property (DebianLike + FreeBSD)
upgraded = (Apt.upgraded `pickOS` Pkg.upgraded)
	`describe` "OS upgraded"

If neither input property supports the targeted OS, calls unsupportedOS. Using the example above on a Fedora system would fail that way.

withOS :: SingI metatypes => Desc -> (OuterMetaTypesWitness '[] -> Maybe System -> Propellor Result) -> Property (MetaTypes metatypes) Source #

Makes a property that is satisfied differently depending on specifics of the host's operating system.

 myproperty :: Property Debian
 myproperty = withOS "foo installed" $ \w o -> case o of
 	(Just (System (Debian kernel (Stable release)) arch)) -> ensureProperty w ...
 	(Just (System (Debian kernel suite) arch)) -> ensureProperty w ...
	_ -> unsupportedOS'

Note that the operating system specifics may not be declared for all hosts, which is where Nothing comes in.

unsupportedOS :: Property UnixLike Source #

A property that always fails with an unsupported OS error.

unsupportedOS' :: HasCallStack => Propellor Result Source #

Throws an error, for use in withOS when a property is lacking support for an OS.

doNothing :: SingI t => Property (MetaTypes t) Source #

A no-op property.

This is the same as mempty from the Monoid instance.

impossible :: SingI t => String -> Property (MetaTypes t) Source #

In situations where it's not possible to provide a property that works, this can be used to make a property that always fails with an error message you provide.

endAction :: Desc -> (Result -> Propellor Result) -> Propellor () Source #

Registers an action that should be run at the very end, after propellor has checks all the properties of a host.

Property result checking

data UncheckedProperty i Source #

This is a Property but its Result is not accurate; in particular it may return NoChange despite having made a change.

However, when it returns MadeChange, it really did make a change, and FailedChange is still an error.

unchecked :: Property i -> UncheckedProperty i Source #

Use to indicate that a Property is unchecked.

changesFile :: Checkable p i => p i -> FilePath -> Property i Source #

Indicates that a Property may change a particular file. When the file is modified in any way (including changing its permissions or mtime), the property will return MadeChange instead of NoChange.

changesFileContent :: Checkable p i => p i -> FilePath -> Property i Source #

Like changesFile, but compares the content of the file. Changes to mtime etc that do not change file content are treated as NoChange.

isNewerThan :: FilePath -> FilePath -> IO Bool Source #

Determines if the first file is newer than the second file.

This can be used with check to only run a command when a file has changed.

check ("/etc/aliases" `isNewerThan` "/etc/aliases.db")
	(cmdProperty "newaliases" [] `assume` MadeChange) -- updates aliases.db

Or it can be used with checkResult to test if a command made a change.

checkResult (return ())
	(\_ -> "/etc/aliases.db" `isNewerThan` "/etc/aliases")
	(cmdProperty "newaliases" [])

(If one of the files does not exist, the file that does exist is considered to be the newer of the two.)

checkResult Source #

Arguments

:: (Checkable p i, LiftPropellor m) 
=> m a

Run before ensuring the property.

-> (a -> m Result)

Run after ensuring the property. Return MadeChange if a change was detected, or NoChange if no change was detected.

-> p i 
-> Property i 

Checks the result of a property. Mostly used to convert a UncheckedProperty to a Property, but can also be used to further check a Property.

class Checkable p i Source #

Minimal complete definition

checkedProp, preCheckedProp

assume :: Checkable p i => p i -> Result -> Property i Source #

Sometimes it's not practical to test if a property made a change. In such a case, it's often fine to say:

someprop `assume` MadeChange

However, beware assuming NoChange, as that will make combinators like onChange not work.