propellor/src/Propellor/Types.hs

153 lines
3.7 KiB
Haskell
Raw Normal View History

{-# LANGUAGE PackageImports #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2014-04-11 01:09:20 +00:00
module Propellor.Types
( Host(..)
2014-06-09 05:45:58 +00:00
, Info
, getInfo
2014-04-11 01:09:20 +00:00
, Propellor(..)
, Property(..)
, RevertableProperty(..)
, IsProp
, describe
, toProp
, requires
, Desc
, Result(..)
, ActionResult(..)
, CmdLine(..)
, PrivDataField(..)
2014-07-06 19:56:56 +00:00
, PrivData
, Context(..)
, anyContext
2014-04-13 01:34:25 +00:00
, SshKeyType(..)
, module Propellor.Types.OS
2014-04-19 01:58:23 +00:00
, module Propellor.Types.Dns
2014-04-11 01:09:20 +00:00
) where
2014-03-30 23:10:32 +00:00
2014-03-31 14:36:45 +00:00
import Data.Monoid
import Control.Applicative
2014-03-31 22:31:08 +00:00
import System.Console.ANSI
2014-11-18 19:05:15 +00:00
import System.Posix.Types
import "mtl" Control.Monad.Reader
import "MonadCatchIO-transformers" Control.Monad.CatchIO
2014-03-31 14:36:45 +00:00
2014-06-09 05:45:58 +00:00
import Propellor.Types.Info
import Propellor.Types.OS
2014-04-19 01:58:23 +00:00
import Propellor.Types.Dns
2014-07-06 19:56:56 +00:00
import Propellor.Types.PrivData
2014-03-30 23:10:32 +00:00
2014-05-31 21:22:35 +00:00
-- | Everything Propellor knows about a system: Its hostname,
2014-06-09 05:45:58 +00:00
-- properties and other info.
2014-05-31 21:22:35 +00:00
data Host = Host
2014-06-01 00:48:23 +00:00
{ hostName :: HostName
, hostProperties :: [Property]
2014-06-09 05:45:58 +00:00
, hostInfo :: Info
2014-05-31 21:22:35 +00:00
}
deriving (Show)
2014-03-30 23:10:32 +00:00
2014-06-09 05:45:58 +00:00
-- | Propellor's monad provides read-only access to info about the host
-- it's running on.
newtype Propellor p = Propellor { runWithHost :: ReaderT Host IO p }
deriving
( Monad
, Functor
, Applicative
, MonadReader Host
, MonadIO
, MonadCatchIO
)
2014-04-11 01:09:20 +00:00
-- | The core data type of Propellor, this represents a property
-- that the system should have, and an action to ensure it has the
-- property.
data Property = Property
{ propertyDesc :: Desc
, propertySatisfy :: Propellor Result
-- ^ must be idempotent; may run repeatedly
2014-06-09 05:45:58 +00:00
, propertyInfo :: Info
-- ^ a property can add info to the host.
}
instance Show Property where
2014-06-05 21:10:16 +00:00
show p = "property " ++ show (propertyDesc p)
2014-04-11 01:09:20 +00:00
-- | A property that can be reverted.
data RevertableProperty = RevertableProperty Property Property
2014-04-02 16:13:39 +00:00
class IsProp p where
-- | Sets description.
describe :: p -> Desc -> p
toProp :: p -> Property
-- | Indicates that the first property can only be satisfied
-- once the second one is.
requires :: p -> Property -> p
2014-06-09 05:45:58 +00:00
getInfo :: p -> Info
2014-04-02 16:13:39 +00:00
instance IsProp Property where
describe p d = p { propertyDesc = d }
toProp p = p
2014-06-09 05:45:58 +00:00
getInfo = propertyInfo
x `requires` y = Property (propertyDesc x) satisfy info
where
2014-10-08 17:17:11 +00:00
info = getInfo y <> getInfo x
satisfy = do
r <- propertySatisfy y
case r of
FailedChange -> return FailedChange
_ -> propertySatisfy x
2014-04-02 16:13:39 +00:00
instance IsProp RevertableProperty where
-- | Sets the description of both sides.
describe (RevertableProperty p1 p2) d =
RevertableProperty (describe p1 d) (describe p2 ("not " ++ d))
toProp (RevertableProperty p1 _) = p1
(RevertableProperty p1 p2) `requires` y =
RevertableProperty (p1 `requires` y) p2
2014-06-09 05:45:58 +00:00
-- | Return the Info of the currently active side.
getInfo (RevertableProperty p1 _p2) = getInfo p1
2014-04-02 16:13:39 +00:00
2014-03-30 23:10:32 +00:00
type Desc = String
data Result = NoChange | MadeChange | FailedChange
deriving (Read, Show, Eq)
2014-03-30 23:10:32 +00:00
2014-03-31 14:36:45 +00:00
instance Monoid Result where
mempty = NoChange
mappend FailedChange _ = FailedChange
mappend _ FailedChange = FailedChange
mappend MadeChange _ = MadeChange
mappend _ MadeChange = MadeChange
mappend NoChange NoChange = NoChange
2014-03-31 22:31:08 +00:00
2014-04-01 20:58:11 +00:00
-- | Results of actions, with color.
2014-03-31 22:31:08 +00:00
class ActionResult a where
getActionResult :: a -> (String, ColorIntensity, Color)
instance ActionResult Bool where
2014-03-31 22:36:53 +00:00
getActionResult False = ("failed", Vivid, Red)
2014-04-02 04:52:39 +00:00
getActionResult True = ("done", Dull, Green)
2014-03-31 22:31:08 +00:00
instance ActionResult Result where
2014-04-02 04:52:39 +00:00
getActionResult NoChange = ("ok", Dull, Green)
2014-03-31 22:31:08 +00:00
getActionResult MadeChange = ("done", Vivid, Green)
getActionResult FailedChange = ("failed", Vivid, Red)
data CmdLine
= Run HostName
| Spin HostName
| SimpleRun HostName
2014-07-06 19:56:56 +00:00
| Set PrivDataField Context
| Dump PrivDataField Context
| Edit PrivDataField Context
| ListFields
| AddKey String
| Continue CmdLine
| Chain HostName Bool
| Update HostName
| Docker HostName
2014-11-18 19:05:15 +00:00
| GitPush Fd Fd
deriving (Read, Show, Eq)