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

Safe HaskellNone
LanguageHaskell98

Propellor.Types

Synopsis

Documentation

data Host Source

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

Constructors

Host 

Instances

Show Host Source 
PropAccum Host Source 
Conductable Host Source 
MonadReader Host Propellor Source 
Conductable [Host] Source

Each host in the list will be conducted in turn. Failure to conduct one host does not prevent conducting subsequent hosts in the list, but will be propagated as an overall failure of the property.

data Property i Source

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

A property can have associated Info or not. This is tracked at the type level with Property NoInfo and Property HasInfo.

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

data Info Source

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

type family CInfo x y Source

Type level calculation of the combination of HasInfo and/or NoInfo

infoProperty Source

Arguments

:: Desc

description of the property

-> Propellor Result

action to run to satisfy the property (must be idempotent; may run repeatedly)

-> Info

info associated with the property

-> [Property i]

child properties

-> Property HasInfo 

Constructs a Property with associated Info.

simpleProperty :: Desc -> Propellor Result -> [Property NoInfo] -> Property NoInfo Source

Constructs a Property with no Info.

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

Changes the action that is performed to satisfy a property.

propertyChildren :: Property i -> [Property i] Source

A Property can include a list of child properties that it also satisfies. This allows them to be introspected to collect their info, etc.

(<!>) :: Property i1 -> Property i2 -> RevertableProperty Source

Shorthand to construct a revertable property.

class IsProp p where Source

Class of types that can be used as properties of a host.

Methods

setDesc :: p -> Desc -> p Source

toProp :: p -> Property HasInfo Source

getDesc :: p -> Desc Source

getInfoRecursive :: p -> Info Source

Gets the info of the property, combined with all info of all children properties.

class Combines x y where Source

Methods

(<<>>) :: x -> y -> CombinedType x y Source

Combines two properties. The second property is ensured first, and only once it is successfully ensures will the first be ensured. The combined property will have the description of the first property.

type family CombinedType x y Source

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

combineWith :: Combines (Property x) (Property y) => (Propellor Result -> Propellor Result -> Propellor Result) -> Property x -> Property y -> CombinedType (Property x) (Property y) Source

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. The two actions to satisfy the properties are passed to a function that can combine them in arbitrary ways.

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 EndAction Source

An action that Propellor runs at the end, after trying to satisfy all properties. It's passed the combined Result of the entire Propellor run.

Constructors

EndAction Desc (Result -> Propellor Result) 

propertySatisfy :: Property i -> Propellor Result Source

Gets the action that can be run to satisfy a Property. You should never run this action directly. Use ensureProperty instead.

ignoreInfo :: Property i -> Property NoInfo Source

Makes a version of a Proprty without its Info. Use with caution!