propellor-2.7.2: 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 

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

Makes a revertable property; the first Property is run normally and the second is run when it's reverted.

class IsProp p where Source

Methods

describe :: p -> Desc -> p Source

Sets description.

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

requires :: x -> y -> CombinedType x y Source

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

type family CombinedType x y Source

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

before :: (IsProp x, Combines y x, IsProp (CombinedType y x)) => x -> y -> CombinedType y x Source

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

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!