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

Safe HaskellNone
LanguageHaskell98

Propellor.Types

Contents

Synopsis

Core data types

data Host Source

Everything Propellor knows about a system: Its hostname, properties and their collected info.

Constructors

Host 

data Property metatypes Source

The core data type of Propellor, this represents a property that the system should have, with a descrition, and an action to ensure it has the property. that have the property.

There are different types of properties that target different OS's, and so have different metatypes. For example: "Property DebianLike" and "Property FreeBSD".

Also, some properties have associated Info, which is indicated in their type: "Property (HasInfo + DebianLike)"

There are many associated type families, which are mostly used internally, so you needn't worry about them.

Constructors

Property metatypes Desc (Propellor Result) Info [ChildProperty] 

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

data RevertableProperty setupmetatypes undometatypes Source

A property that can be reverted. The first Property is run normally and the second is run when it's reverted.

Constructors

RevertableProperty 

Fields

setupRevertableProperty :: Property setupmetatypes
 
undoRevertableProperty :: Property undometatypes
 

Instances

((~) CheckCombine (CheckCombinable k x y) CanCombine, SingI [k] (Combine k x y)) => Combines (Property (MetaTypes [k] x)) (RevertableProperty (MetaTypes [k] y) (MetaTypes k y')) Source 
Show (RevertableProperty setupmetatypes undometatypes) Source 
IsProp (RevertableProperty setupmetatypes undometatypes) Source 
((~) CheckCombine (CheckCombinable k x y) CanCombine, SingI [k] (Combine k x y)) => Combines (RevertableProperty (MetaTypes [k] x) (MetaTypes k x')) (Property (MetaTypes [k] y)) Source 
((~) CheckCombine (CheckCombinable k x y) CanCombine, (~) CheckCombine (CheckCombinable k1 x' y') CanCombine, SingI [k] (Combine k x y), SingI [k1] (Combine k1 x' y')) => Combines (RevertableProperty (MetaTypes [k] x) (MetaTypes [k] x')) (RevertableProperty (MetaTypes [k] y) (MetaTypes [k] y')) Source 
type CombinedType (Property (MetaTypes [k] x)) (RevertableProperty (MetaTypes [k] y) (MetaTypes k1 y')) = Property (MetaTypes [k] (Combine k x y)) Source 
type CombinedType (RevertableProperty (MetaTypes [k] x) (MetaTypes k1 x')) (Property (MetaTypes [k] y)) = Property (MetaTypes [k] (Combine k x y)) Source 
type CombinedType (RevertableProperty (MetaTypes [k] x) (MetaTypes [k1] x')) (RevertableProperty (MetaTypes [k] y) (MetaTypes [k1] y')) = RevertableProperty (MetaTypes [k] (Combine k x y)) (MetaTypes [k1] (Combine k1 x' y')) Source 

(<!>) :: Property setupmetatypes -> Property undometatypes -> RevertableProperty setupmetatypes undometatypes Source

Shorthand to construct a revertable property from any two Properties.

newtype 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.

Constructors

Propellor 

Fields

runWithHost :: RWST Host [EndAction] () IO p
 

data Info Source

Information about a Host, which can be provided by its properties.

Many different types of data can be contained in the same Info value at the same time. See toInfo and fromInfo.

Types of properties

type DebianLike = MetaTypes `[Targeting OSDebian, Targeting OSBuntish]` Source

Debian and derivatives.

type HasInfo = MetaTypes `[WithInfo]` Source

Used to indicate that a Property adds Info to the Host where it's used.

type family a + b :: ab Source

Convenience type operator to combine two MetaTypes lists.

For example:

HasInfo + Debian

Which is shorthand for this type:

MetaTypes '[WithInfo, Targeting OSDebian]

Instances

type (+) * (MetaTypes [k] a) (MetaTypes [k] b) Source 

class TightenTargets p where Source

Methods

tightenTargets :: ((Targets untightened `NotSuperset` Targets tightened) ~ CanCombine, (NonTargets tightened `NotSuperset` NonTargets untightened) ~ CanCombine, SingI tightened) => p (MetaTypes untightened) -> p (MetaTypes tightened) Source

Tightens the MetaType list of a Property (or similar), to contain fewer targets.

For example, to make a property that uses apt-get, which is only available on DebianLike systems:

upgraded :: Property DebianLike
upgraded = tightenTargets $ cmdProperty "apt-get" ["upgrade"]

Combining and modifying properties

class Combines x y where Source

Methods

combineWith Source

Arguments

:: ResultCombiner

How to combine the actions to satisfy the properties.

-> ResultCombiner

Used when combining revertable properties, to combine their reversion actions.

-> x 
-> y 
-> CombinedType x y 

Combines together two properties, yielding a property that has the description and info of the first, and that has the second property as a child property.

type family CombinedType x y Source

Type level calculation of the type that results from combining two types of properties.

Instances

adjustPropertySatisfy :: Property metatypes -> (Propellor Result -> Propellor Result) -> Property metatypes Source

Changes the action that is performed to satisfy a property.

Other included types