propellor/src/Propellor/Attr.hs

101 lines
3.0 KiB
Haskell
Raw Normal View History

2014-04-11 01:09:20 +00:00
{-# LANGUAGE PackageImports #-}
module Propellor.Attr where
import Propellor.Types
import Propellor.Types.Attr
import "mtl" Control.Monad.Reader
import qualified Data.Set as S
import qualified Data.Map as M
import Data.Maybe
2014-04-13 06:28:40 +00:00
import Control.Applicative
2014-04-11 01:09:20 +00:00
pureAttrProperty :: Desc -> SetAttr -> Property
pureAttrProperty desc = Property ("has " ++ desc) (return NoChange)
2014-04-11 01:09:20 +00:00
getHostName :: Propellor HostName
getHostName = asks _hostName
2014-04-11 01:09:20 +00:00
os :: System -> Property
os system = pureAttrProperty ("Operating " ++ show system) $
\d -> d { _os = Just system }
getOS :: Propellor (Maybe System)
getOS = asks (_os . hostAttr)
-- | Indidate that a host has an A record in the DNS.
--
-- TODO check at run time if the host really has this address.
-- (Can't change the host's address, but as a sanity check.)
ipv4 :: String -> Property
2014-05-31 20:48:14 +00:00
ipv4 = addDNS . Address . IPv4
-- | Indidate that a host has an AAAA record in the DNS.
ipv6 :: String -> Property
2014-05-31 20:48:14 +00:00
ipv6 = addDNS . Address . IPv6
-- | Indicates another name for the host in the DNS.
2014-04-19 05:28:46 +00:00
alias :: Domain -> Property
2014-05-31 20:48:14 +00:00
alias = addDNS . CNAME . AbsDomain
2014-04-11 01:09:20 +00:00
2014-05-31 20:48:14 +00:00
addDNS :: Record -> Property
addDNS r = pureAttrProperty (rdesc r) $
\d -> d { _dns = S.insert r (_dns d) }
where
rdesc (CNAME d) = unwords ["alias", ddesc d]
rdesc (Address (IPv4 addr)) = unwords ["ipv4", addr]
rdesc (Address (IPv6 addr)) = unwords ["ipv6", addr]
rdesc (MX n d) = unwords ["MX", show n, ddesc d]
rdesc (NS d) = unwords ["NS", ddesc d]
rdesc (TXT s) = unwords ["TXT", s]
rdesc (SRV x y z d) = unwords ["SRV", show x, show y, show z, ddesc d]
ddesc (AbsDomain domain) = domain
ddesc (RelDomain domain) = domain
ddesc RootDomain = "@"
2014-04-11 01:09:20 +00:00
-- | Adds a DNS NamedConf stanza.
--
-- Note that adding a Master stanza for a domain always overrides an
-- existing Secondary stanza, while a Secondary stanza is only added
-- when there is no existing Master stanza.
addNamedConf :: NamedConf -> SetAttr
addNamedConf conf d = d { _namedconf = new }
where
m = _namedconf d
domain = confDomain conf
2014-04-23 19:04:35 +00:00
new = case (confDnsServerType conf, confDnsServerType <$> M.lookup domain m) of
(Secondary, Just Master) -> m
_ -> M.insert domain conf m
getNamedConf :: Propellor (M.Map Domain NamedConf)
getNamedConf = asks (_namedconf . hostAttr)
sshPubKey :: String -> Property
2014-04-13 06:28:40 +00:00
sshPubKey k = pureAttrProperty ("ssh pubkey known") $
\d -> d { _sshPubKey = Just k }
getSshPubKey :: Propellor (Maybe String)
getSshPubKey = asks (_sshPubKey . hostAttr)
2014-04-13 06:28:40 +00:00
2014-04-11 01:09:20 +00:00
hostAttr :: Host -> Attr
hostAttr (Host _ _ mkattrs) = mkattrs newAttr
2014-04-11 01:09:20 +00:00
hostProperties :: Host -> [Property]
2014-05-31 21:22:35 +00:00
hostProperties (Host _ ps _) = ps
2014-04-11 01:09:20 +00:00
hostMap :: [Host] -> M.Map HostName Host
2014-05-31 21:22:35 +00:00
hostMap l = M.fromList $ zip (map _hostName l) l
2014-04-11 01:09:20 +00:00
findHost :: [Host] -> HostName -> Maybe Host
findHost l hn = M.lookup hn (hostMap l)
2014-04-13 06:28:40 +00:00
getAddresses :: Attr -> [IPAddr]
getAddresses = mapMaybe getIPAddr . S.toList . _dns
hostAddresses :: HostName -> [Host] -> [IPAddr]
hostAddresses hn hosts = case hostAttr <$> findHost hosts hn of
Nothing -> []
Just attr -> mapMaybe getIPAddr $ S.toList $ _dns attr