summaryrefslogtreecommitdiff
path: root/src/Propellor/PropAccum.hs
diff options
context:
space:
mode:
authorJoey Hess2016-03-28 05:53:38 -0400
committerJoey Hess2016-03-28 05:55:48 -0400
commita1655d24bbb1db9caccdf93eae8110d746389ae2 (patch)
tree66b6890d852c19daec2306920fecf9108e055273 /src/Propellor/PropAccum.hs
parentebf30061d8f8a251330070e69c2710fe4a8fd9da (diff)
type safe targets for properties
* Property types have been improved to indicate what systems they target. This prevents using eg, Property FreeBSD on a Debian system. Transition guide for this sweeping API change: - Change "host name & foo & bar" to "host name $ props & foo & bar" - Similarly, `propertyList` and `combineProperties` need `props` to be used to combine together properties; they no longer accept lists of properties. (If you have such a list, use `toProps`.) - And similarly, Chroot, Docker, and Systemd container need `props` to be used to combine together the properies used inside them. - The `os` property is removed. Instead use `osDebian`, `osBuntish`, or `osFreeBSD`. These tell the type checker the target OS of a host. - Change "Property NoInfo" to "Property UnixLike" - Change "Property HasInfo" to "Property (HasInfo + UnixLike)" - Change "RevertableProperty NoInfo" to "RevertableProperty UnixLike UnixLike" - Change "RevertableProperty HasInfo" to "RevertableProperty (HasInfo + UnixLike) UnixLike" - GHC needs {-# LANGUAGE TypeOperators #-} to use these fancy types. This is enabled by default for all modules in propellor.cabal. But if you are using propellor as a library, you may need to enable it manually. - If you know a property only works on a particular OS, like Debian or FreeBSD, use that instead of "UnixLike". For example: "Property Debian" - It's also possible make a property support a set of OS's, for example: "Property (Debian + FreeBSD)" - Removed `infoProperty` and `simpleProperty` constructors, instead use `property` to construct a Property. - Due to the polymorphic type returned by `property`, additional type signatures tend to be needed when using it. For example, this will fail to type check, because the type checker cannot guess what type you intend the intermediate property "go" to have: foo :: Property UnixLike foo = go `requires` bar where go = property "foo" (return NoChange) To fix, specify the type of go: go :: Property UnixLike - `ensureProperty` now needs to be passed a witness to the type of the property it's used in. change this: foo = property desc $ ... ensureProperty bar to this: foo = property' desc $ \w -> ... ensureProperty w bar - General purpose properties like cmdProperty have type "Property UnixLike". When using that to run a command only available on Debian, you can tighten the type to only the OS that your more specific property works on. For example: upgraded :: Property Debian upgraded = tightenTargets (cmdProperty "apt-get" ["upgrade"]) - Several utility functions have been renamed: getInfo to fromInfo propertyInfo to getInfo propertyDesc to getDesc propertyChildren to getChildren * The new `pickOS` property combinator can be used to combine different properties, supporting different OS's, into one Property that chooses which to use based on the Host's OS. * Re-enabled -O0 in propellor.cabal to reign in ghc's memory use handling these complex new types. * Added dependency on concurrent-output; removed embedded copy.
Diffstat (limited to 'src/Propellor/PropAccum.hs')
-rw-r--r--src/Propellor/PropAccum.hs122
1 files changed, 60 insertions, 62 deletions
diff --git a/src/Propellor/PropAccum.hs b/src/Propellor/PropAccum.hs
index 85a30af5..d9fa8ec7 100644
--- a/src/Propellor/PropAccum.hs
+++ b/src/Propellor/PropAccum.hs
@@ -1,88 +1,86 @@
-{-# LANGUAGE PackageImports, FlexibleContexts #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE DataKinds #-}
module Propellor.PropAccum
( host
- , PropAccum(..)
+ , Props(..)
+ , props
, (&)
, (&^)
, (!)
- , propagateContainer
) where
-import Data.Monoid
-
import Propellor.Types
+import Propellor.Types.MetaTypes
+import Propellor.Types.Core
import Propellor.Property
-import Propellor.Types.Info
-import Propellor.PrivData
--- | Starts accumulating the properties of a Host.
+import Data.Monoid
+import Prelude
+
+-- | Defines a host and its properties.
--
--- > host "example.com"
+-- > host "example.com" $ props
-- > & someproperty
-- > ! oldproperty
-- > & otherproperty
-host :: HostName -> Host
-host hn = Host hn [] mempty
+host :: HostName -> Props metatypes -> Host
+host hn (Props ps) = Host hn ps (mconcat (map getInfoRecursive ps))
--- | Something that can accumulate properties.
-class PropAccum h where
- -- | Adds a property.
- addProp :: IsProp p => h -> p -> h
+-- | Start accumulating a list of properties.
+--
+-- Properties can be added to it using `(&)` etc.
+props :: Props UnixLike
+props = Props []
- -- | Like addProp, but adds the property at the front of the list.
- addPropFront :: IsProp p => h -> p -> h
+infixl 1 &
+infixl 1 &^
+infixl 1 !
- getProperties :: h -> [Property HasInfo]
+type family GetMetaTypes x
+type instance GetMetaTypes (Property (MetaTypes t)) = MetaTypes t
+type instance GetMetaTypes (RevertableProperty (MetaTypes t) undo) = MetaTypes t
--- | Adds a property to a `Host` or other `PropAccum`
+-- | Adds a property to a Props.
--
-- Can add Properties and RevertableProperties
-(&) :: (PropAccum h, IsProp p) => h -> p -> h
-(&) = addProp
+(&)
+ ::
+ ( IsProp p
+ , MetaTypes y ~ GetMetaTypes p
+ , CheckCombinable x y ~ 'CanCombine
+ )
+ => Props (MetaTypes x)
+ -> p
+ -> Props (MetaTypes (Combine x y))
+Props c & p = Props (c ++ [toChildProperty p])
-- | Adds a property before any other properties.
-(&^) :: (PropAccum h, IsProp p) => h -> p -> h
-(&^) = addPropFront
+(&^)
+ ::
+ ( IsProp p
+ , MetaTypes y ~ GetMetaTypes p
+ , CheckCombinable x y ~ 'CanCombine
+ )
+ => Props (MetaTypes x)
+ -> p
+ -> Props (MetaTypes (Combine x y))
+Props c &^ p = Props (toChildProperty p : c)
-- | Adds a property in reverted form.
-(!) :: IsProp (RevertableProperty i) => PropAccum h => h -> RevertableProperty i -> h
-h ! p = h & revert p
+(!)
+ :: (CheckCombinable x z ~ 'CanCombine)
+ => Props (MetaTypes x)
+ -> RevertableProperty (MetaTypes y) (MetaTypes z)
+ -> Props (MetaTypes (Combine x z))
+Props c ! p = Props (c ++ [toChildProperty (revert p)])
-infixl 1 &
-infixl 1 &^
-infixl 1 !
-
-instance PropAccum Host where
- (Host hn ps is) `addProp` p = Host hn (ps ++ [toProp p])
- (is <> getInfoRecursive p)
- (Host hn ps is) `addPropFront` p = Host hn (toProp p : ps)
- (getInfoRecursive p <> is)
- getProperties = hostProperties
-
--- | Adjust the provided Property, adding to its
--- propertyChidren the properties of the provided container.
---
--- The Info of the propertyChildren is adjusted to only include
--- info that should be propagated out to the Property.
---
--- Any PrivInfo that uses HostContext is adjusted to use the name
--- of the container as its context.
-propagateContainer
- :: (PropAccum container)
- => String
- -> container
- -> Property HasInfo
- -> Property HasInfo
-propagateContainer containername c prop = infoProperty
- (propertyDesc prop)
- (propertySatisfy prop)
- (propertyInfo prop)
- (propertyChildren prop ++ hostprops)
- where
- hostprops = map go $ getProperties c
- go p =
- let i = mapInfo (forceHostContext containername)
- (propagatableInfo (propertyInfo p))
- cs = map go (propertyChildren p)
- in infoProperty (propertyDesc p) (propertySatisfy p) i cs
+-- addPropsHost :: Host -> [Prop] -> Host
+-- addPropsHost (Host hn ps i) p = Host hn ps' i'
+-- where
+-- ps' = ps ++ [toChildProperty p]
+-- i' = i <> getInfoRecursive p