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

Safe HaskellNone
LanguageHaskell98

Propellor.Types.Core

Synopsis

Documentation

data Host Source #

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

Constructors

Host 

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

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 #

(*>) :: 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 #

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 #

class LiftPropellor m where Source #

Minimal complete definition

liftPropellor

Methods

liftPropellor :: m a -> Propellor a Source #

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) 

data Props metatypes Source #

Props is a combination of a list of properties, with their combined metatypes.

Constructors

Props [ChildProperty] 

class IsProp p where Source #

Methods

setDesc :: p -> Desc -> p Source #

getDesc :: p -> Desc Source #

getChildren :: p -> [ChildProperty] Source #

addChildren :: p -> [ChildProperty] -> p Source #

getInfoRecursive :: p -> Info Source #

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

getInfo :: p -> Info Source #

Info, not including info from children.

toChildProperty :: p -> ChildProperty Source #

Gets a ChildProperty representing the Property. You should not normally need to use this.

getSatisfy :: p -> Maybe (Propellor Result) Source #

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

Instances

IsProp ChildProperty Source # 
IsProp (Property metatypes) Source # 

Methods

setDesc :: Property metatypes -> Desc -> Property metatypes Source #

getDesc :: Property metatypes -> Desc Source #

getChildren :: Property metatypes -> [ChildProperty] Source #

addChildren :: Property metatypes -> [ChildProperty] -> Property metatypes Source #

getInfoRecursive :: Property metatypes -> Info Source #

getInfo :: Property metatypes -> Info Source #

toChildProperty :: Property metatypes -> ChildProperty Source #

getSatisfy :: Property metatypes -> Maybe (Propellor Result) Source #

IsProp (RevertableProperty setupmetatypes undometatypes) Source # 

Methods

setDesc :: RevertableProperty setupmetatypes undometatypes -> Desc -> RevertableProperty setupmetatypes undometatypes Source #

getDesc :: RevertableProperty setupmetatypes undometatypes -> Desc Source #

getChildren :: RevertableProperty setupmetatypes undometatypes -> [ChildProperty] Source #

addChildren :: RevertableProperty setupmetatypes undometatypes -> [ChildProperty] -> RevertableProperty setupmetatypes undometatypes Source #

getInfoRecursive :: RevertableProperty setupmetatypes undometatypes -> Info Source #

getInfo :: RevertableProperty setupmetatypes undometatypes -> Info Source #

toChildProperty :: RevertableProperty setupmetatypes undometatypes -> ChildProperty Source #

getSatisfy :: RevertableProperty setupmetatypes undometatypes -> Maybe (Propellor Result) Source #