summaryrefslogtreecommitdiff
path: root/src/Propellor/Types/Info.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Propellor/Types/Info.hs')
-rw-r--r--src/Propellor/Types/Info.hs23
1 files changed, 13 insertions, 10 deletions
diff --git a/src/Propellor/Types/Info.hs b/src/Propellor/Types/Info.hs
index 2e188ae5..6716c403 100644
--- a/src/Propellor/Types/Info.hs
+++ b/src/Propellor/Types/Info.hs
@@ -1,13 +1,14 @@
{-# LANGUAGE GADTs, DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
module Propellor.Types.Info (
- Info,
+ Info(..),
+ InfoEntry(..),
IsInfo(..),
+ PropagateInfo(..),
addInfo,
toInfo,
fromInfo,
mapInfo,
- propagatableInfo,
InfoVal(..),
fromInfoVal,
Typeable,
@@ -16,6 +17,7 @@ module Propellor.Types.Info (
import Data.Dynamic
import Data.Maybe
import Data.Monoid
+import qualified Data.Typeable as T
import Prelude
-- | Information about a Host, which can be provided by its properties.
@@ -34,7 +36,7 @@ instance Show InfoEntry where
-- Extracts the value from an InfoEntry but only when
-- it's of the requested type.
extractInfoEntry :: Typeable v => InfoEntry -> Maybe v
-extractInfoEntry (InfoEntry v) = cast v
+extractInfoEntry (InfoEntry v) = T.cast v
-- | Values stored in Info must be members of this class.
--
@@ -44,7 +46,13 @@ extractInfoEntry (InfoEntry v) = cast v
class (Typeable v, Monoid v, Show v) => IsInfo v where
-- | Should info of this type be propagated out of a
-- container to its Host?
- propagateInfo :: v -> Bool
+ propagateInfo :: v -> PropagateInfo
+
+data PropagateInfo
+ = PropagateInfo Bool
+ | PropagatePrivData
+ -- ^ Info about PrivData generally will be propigated even in cases
+ -- where other Info is not, so it treated specially.
-- | Any value in the `IsInfo` type class can be added to an Info.
addInfo :: IsInfo v => Info -> v -> Info
@@ -68,11 +76,6 @@ mapInfo f (Info l) = Info (map go l)
Nothing -> i
Just v -> InfoEntry (f v)
--- | Filters out parts of the Info that should not propagate out of a
--- container.
-propagatableInfo :: Info -> Info
-propagatableInfo (Info l) = Info (filter (\(InfoEntry a) -> propagateInfo a) l)
-
-- | Use this to put a value in Info that is not a monoid.
-- The last value set will be used. This info does not propagate
-- out of a container.
@@ -85,7 +88,7 @@ instance Monoid (InfoVal v) where
mappend v NoInfoVal = v
instance (Typeable v, Show v) => IsInfo (InfoVal v) where
- propagateInfo _ = False
+ propagateInfo _ = PropagateInfo False
fromInfoVal :: InfoVal v -> Maybe v
fromInfoVal NoInfoVal = Nothing