Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Host = Host {
- hostName :: HostName
- hostProperties :: [ChildProperty]
- hostInfo :: Info
- data Property metatypes = Property metatypes Desc (Maybe (Propellor Result)) Info [ChildProperty]
- property :: SingI metatypes => Desc -> Propellor Result -> Property (MetaTypes metatypes)
- property'' :: SingI metatypes => Desc -> Maybe (Propellor Result) -> Property (MetaTypes metatypes)
- type Desc = String
- data RevertableProperty setupmetatypes undometatypes = RevertableProperty {
- setupRevertableProperty :: Property setupmetatypes
- undoRevertableProperty :: Property undometatypes
- (<!>) :: Property setupmetatypes -> Property undometatypes -> RevertableProperty setupmetatypes undometatypes
- newtype Propellor p = Propellor {
- runWithHost :: RWST Host [EndAction] () IO p
- class LiftPropellor m where
- liftPropellor :: m a -> Propellor a
- data Info
- type UnixLike = MetaTypes '['Targeting 'OSDebian, 'Targeting 'OSBuntish, 'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
- type Linux = MetaTypes '['Targeting 'OSDebian, 'Targeting 'OSBuntish, 'Targeting 'OSArchLinux]
- type DebianLike = MetaTypes '['Targeting 'OSDebian, 'Targeting 'OSBuntish]
- type Debian = MetaTypes '['Targeting 'OSDebian]
- type Buntish = MetaTypes '['Targeting 'OSBuntish]
- type ArchLinux = MetaTypes '['Targeting 'OSArchLinux]
- type FreeBSD = MetaTypes '['Targeting 'OSFreeBSD]
- type HasInfo = MetaTypes '['WithInfo]
- type family a + b :: Type where ...
- class TightenTargets p where
- tightenTargets :: (TightenTargetsAllowed untightened tightened, SingI tightened) => p (MetaTypes untightened) -> p (MetaTypes tightened)
- type family TightenTargetsAllowed untightened tightened :: Constraint where ...
- class Combines x y where
- combineWith :: ResultCombiner -> ResultCombiner -> x -> y -> CombinedType x y
- type family CombinedType x y where ...
- type ResultCombiner = Maybe (Propellor Result) -> Maybe (Propellor Result) -> Maybe (Propellor Result)
- adjustPropertySatisfy :: Property metatypes -> (Propellor Result -> Propellor Result) -> Property metatypes
- module Propellor.Types.OS
- module Propellor.Types.ConfigurableValue
- module Propellor.Types.Dns
- module Propellor.Types.Result
- module Propellor.Types.ZFS
Core data types
Everything Propellor knows about a system: Its hostname, properties and their collected info.
Host | |
|
Instances
Show Host Source # | |
IsContainer Host Source # | |
Defined in Propellor.Container containerProperties :: Host -> [ChildProperty] Source # containerInfo :: Host -> Info Source # setContainerProperties :: Host -> [ChildProperty] -> Host Source # | |
Conductable Host Source # | |
MonadReader Host Propellor Source # | |
Conductable [Host] Source # | |
data Property metatypes Source #
The core data type of Propellor, this represents a property that the system should have, with a description, 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.
Instances
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.
RevertableProperty | |
|
Instances
(<!>) :: Property setupmetatypes -> Property undometatypes -> RevertableProperty setupmetatypes undometatypes Source #
Shorthand to construct a revertable property from any two Properties.
Propellor's monad provides read-only access to info about the host it's running on, and a writer to accumulate EndActions.
Instances
MonadIO Propellor Source # | |
Defined in Propellor.Types.Core | |
Applicative Propellor Source # | |
Functor Propellor Source # | |
Monad Propellor Source # | |
MonadCatch Propellor Source # | |
MonadMask Propellor Source # | |
Defined in Propellor.Types.Core | |
MonadThrow Propellor Source # | |
Defined in Propellor.Types.Core | |
LiftPropellor Propellor Source # | |
Defined in Propellor.Types.Core liftPropellor :: Propellor a -> Propellor a Source # | |
MonadReader Host Propellor Source # | |
Monoid (Propellor Result) Source # | |
Semigroup (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 # | |
class LiftPropellor m where Source #
liftPropellor :: m a -> Propellor a Source #
Instances
LiftPropellor IO Source # | |
Defined in Propellor.Types.Core liftPropellor :: IO a -> Propellor a Source # | |
LiftPropellor Propellor Source # | |
Defined in Propellor.Types.Core liftPropellor :: Propellor a -> Propellor a 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 UnixLike = MetaTypes '['Targeting 'OSDebian, 'Targeting 'OSBuntish, 'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD] Source #
Any unix-like system
type Linux = MetaTypes '['Targeting 'OSDebian, 'Targeting 'OSBuntish, 'Targeting 'OSArchLinux] Source #
Any linux system
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 :: Type where ... Source #
Convenience type operator to combine two MetaTypes
lists.
For example:
HasInfo + Debian
Which is shorthand for this type:
MetaTypes '[WithInfo, Targeting OSDebian]
class TightenTargets p where Source #
tightenTargets :: (TightenTargetsAllowed untightened tightened, 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 # | |
Defined in Propellor.Types | |
TightenTargets UncheckedProperty Source # | |
Defined in Propellor.Types.ResultCheck tightenTargets :: forall (untightened :: [MetaType]) (tightened :: [MetaType]). (TightenTargetsAllowed untightened tightened, SingI tightened) => UncheckedProperty (MetaTypes untightened) -> UncheckedProperty (MetaTypes tightened) Source # |
type family TightenTargetsAllowed untightened tightened :: Constraint where ... Source #
TightenTargetsAllowed untightened tightened = If ((Targets tightened `IsSubset` Targets untightened) && (NonTargets untightened `IsSubset` NonTargets tightened)) ('True ~ 'True) (IfStuck (Targets tightened) (DelayError ('Text "Unable to infer desired Property type in this use of tightenTargets." :$$: 'Text "Consider adding a type annotation.")) (DelayErrorFcf ('Text "This use of tightenTargets would widen, not narrow, adding: " :$$: PrettyPrintMetaTypes (Difference (Targets tightened) (Targets untightened))))) |
Combining and modifying properties
class Combines x y where Source #
:: 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
type family CombinedType x y where ... Source #
Type level calculation of the type that results from combining two types of properties.
CombinedType (Property (MetaTypes x)) (Property (MetaTypes y)) = Property (MetaTypes (Combine x y)) | |
CombinedType (RevertableProperty (MetaTypes x) (MetaTypes x')) (RevertableProperty (MetaTypes y) (MetaTypes y')) = RevertableProperty (MetaTypes (Combine x y)) (MetaTypes (Combine x' y')) | |
CombinedType (RevertableProperty (MetaTypes x) (MetaTypes x')) (Property (MetaTypes y)) = Property (MetaTypes (Combine x y)) | |
CombinedType (Property (MetaTypes x)) (RevertableProperty (MetaTypes y) (MetaTypes y')) = Property (MetaTypes (Combine x y)) |
type ResultCombiner = Maybe (Propellor Result) -> Maybe (Propellor Result) -> Maybe (Propellor Result) Source #
adjustPropertySatisfy :: Property metatypes -> (Propellor Result -> Propellor Result) -> Property metatypes Source #
Changes the action that is performed to satisfy a property.
Other included types
module Propellor.Types.OS
module Propellor.Types.Dns
module Propellor.Types.Result
module Propellor.Types.ZFS