propellor-5.6.1: 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.

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 (Maybe (Propellor Result)) Info [ChildProperty] 
Instances
TightenTargets Property Source # 
Instance details

Defined in Propellor.Types

Methods

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

Checkable Property i Source # 
Instance details

Defined in Propellor.Types.ResultCheck

Show (Property metatypes) Source # 
Instance details

Defined in Propellor.Types

Methods

showsPrec :: Int -> Property metatypes -> ShowS #

show :: Property metatypes -> String #

showList :: [Property metatypes] -> ShowS #

SingI metatypes => Semigroup (Property (MetaTypes metatypes)) Source #

Any type of Property is a Semigroup. When properties x and y are appended together, the resulting property has a description like "x and y". Note that when x fails to be ensured, it will not try to ensure y.

Instance details

Defined in Propellor.Types

Methods

(<>) :: Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) #

sconcat :: NonEmpty (Property (MetaTypes metatypes)) -> Property (MetaTypes metatypes) #

stimes :: Integral b => b -> Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) #

SingI metatypes => Monoid (Property (MetaTypes metatypes)) Source #

Any type of Property is a Monoid.

Instance details

Defined in Propellor.Types

Methods

mempty :: Property (MetaTypes metatypes) #

mappend :: Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) -> Property (MetaTypes metatypes) #

mconcat :: [Property (MetaTypes metatypes)] -> Property (MetaTypes metatypes) #

IsProp (Property metatypes) Source # 
Instance details

Defined in Propellor.Types

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 #

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (Property (MetaTypes x)) (Property (MetaTypes y)) Source # 
Instance details

Defined in Propellor.Types

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (Property (MetaTypes x)) (RevertableProperty (MetaTypes y) (MetaTypes y')) Source # 
Instance details

Defined in Propellor.Types

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (RevertableProperty (MetaTypes x) (MetaTypes x')) (Property (MetaTypes y)) Source # 
Instance details

Defined in Propellor.Types

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 -> Maybe (Propellor Result) -> Property (MetaTypes metatypes) Source #

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.

See Versioned for a way to use RevertableProperty to define different versions of a host.

Constructors

RevertableProperty 

Fields

Instances
(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (Property (MetaTypes x)) (RevertableProperty (MetaTypes y) (MetaTypes y')) Source # 
Instance details

Defined in Propellor.Types

Show (RevertableProperty setupmetatypes undometatypes) Source # 
Instance details

Defined in Propellor.Types

Methods

showsPrec :: Int -> RevertableProperty setupmetatypes undometatypes -> ShowS #

show :: RevertableProperty setupmetatypes undometatypes -> String #

showList :: [RevertableProperty setupmetatypes undometatypes] -> ShowS #

(Semigroup (Property (MetaTypes setupmetatypes)), Semigroup (Property (MetaTypes undometatypes)), SingI setupmetatypes, SingI undometatypes) => Semigroup (RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes)) Source #

Any type of RevertableProperty is a Semigroup. When revertable properties x and y are appended together, the resulting revertable property has a description like "x and y". Note that when x fails to be ensured, it will not try to ensure y.

Instance details

Defined in Propellor.Types

Methods

(<>) :: RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

sconcat :: NonEmpty (RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes)) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

stimes :: Integral b => b -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

(Monoid (Property (MetaTypes setupmetatypes)), Monoid (Property (MetaTypes undometatypes)), SingI setupmetatypes, SingI undometatypes) => Monoid (RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes)) Source # 
Instance details

Defined in Propellor.Types

Methods

mempty :: RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

mappend :: RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

mconcat :: [RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes)] -> RevertableProperty (MetaTypes setupmetatypes) (MetaTypes undometatypes) #

IsProp (RevertableProperty setupmetatypes undometatypes) Source # 
Instance details

Defined in Propellor.Types

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 #

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (RevertableProperty (MetaTypes x) (MetaTypes x')) (Property (MetaTypes y)) Source # 
Instance details

Defined in Propellor.Types

(CheckCombinable x y ~ CanCombine, CheckCombinable x' y' ~ CanCombine, SingI (Combine x y), SingI (Combine x' y')) => Combines (RevertableProperty (MetaTypes x) (MetaTypes x')) (RevertableProperty (MetaTypes y) (MetaTypes y')) Source # 
Instance details

Defined in Propellor.Types

(<!>) :: 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

Instances
Monad Propellor Source # 
Instance details

Defined in Propellor.Types.Core

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 # 
Instance details

Defined in Propellor.Types.Core

Methods

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

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

Applicative Propellor Source # 
Instance details

Defined in Propellor.Types.Core

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 # 
Instance details

Defined in Propellor.Types.Core

Methods

liftIO :: IO a -> Propellor a #

MonadThrow Propellor Source # 
Instance details

Defined in Propellor.Types.Core

Methods

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

MonadCatch Propellor Source # 
Instance details

Defined in Propellor.Types.Core

Methods

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

MonadMask Propellor Source # 
Instance details

Defined in Propellor.Types.Core

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 # 
Instance details

Defined in Propellor.Types.Core

MonadReader Host Propellor Source # 
Instance details

Defined in Propellor.Types.Core

Methods

ask :: Propellor Host #

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

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

Semigroup (Propellor Result) Source #

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

Instance details

Defined in Propellor.Types.Core

Monoid (Propellor Result) Source # 
Instance details

Defined in Propellor.Types.Core

MonadWriter [EndAction] Propellor Source # 
Instance details

Defined in Propellor.Types.Core

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 #

Methods

liftPropellor :: m a -> Propellor a Source #

Instances
LiftPropellor IO Source # 
Instance details

Defined in Propellor.Types.Core

Methods

liftPropellor :: IO a -> Propellor a Source #

LiftPropellor Propellor Source # 
Instance details

Defined in Propellor.Types.Core

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.

Instances
Show Info Source # 
Instance details

Defined in Propellor.Types.Info

Methods

showsPrec :: Int -> Info -> ShowS #

show :: Info -> String #

showList :: [Info] -> ShowS #

Semigroup Info Source # 
Instance details

Defined in Propellor.Types.Info

Methods

(<>) :: Info -> Info -> Info #

sconcat :: NonEmpty Info -> Info #

stimes :: Integral b => b -> Info -> Info #

Monoid Info Source # 
Instance details

Defined in Propellor.Types.Info

Methods

mempty :: Info #

mappend :: Info -> Info -> Info #

mconcat :: [Info] -> Info #

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 :: * where ... Source #

Convenience type operator to combine two MetaTypes lists.

For example:

HasInfo + Debian

Which is shorthand for this type:

MetaTypes '[WithInfo, Targeting OSDebian]

Equations

(MetaTypes a) + (MetaTypes b) = MetaTypes (Concat a b) 

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"]
Instances
TightenTargets Property Source # 
Instance details

Defined in Propellor.Types

Methods

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

TightenTargets UncheckedProperty Source # 
Instance details

Defined in Propellor.Types.ResultCheck

Methods

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

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.

Instances
(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (Property (MetaTypes x)) (Property (MetaTypes y)) Source # 
Instance details

Defined in Propellor.Types

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (Property (MetaTypes x)) (RevertableProperty (MetaTypes y) (MetaTypes y')) Source # 
Instance details

Defined in Propellor.Types

(CheckCombinable x y ~ CanCombine, SingI (Combine x y)) => Combines (RevertableProperty (MetaTypes x) (MetaTypes x')) (Property (MetaTypes y)) Source # 
Instance details

Defined in Propellor.Types

(CheckCombinable x y ~ CanCombine, CheckCombinable x' y' ~ CanCombine, SingI (Combine x y), SingI (Combine x' y')) => Combines (RevertableProperty (MetaTypes x) (MetaTypes x')) (RevertableProperty (MetaTypes y) (MetaTypes y')) Source # 
Instance details

Defined in Propellor.Types

type family CombinedType x y where ... Source #

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

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

Changes the action that is performed to satisfy a property.

Other included types