Dns.primary wrote, not quite ready
This commit is contained in:
parent
c8a3653775
commit
395d3f206a
|
@ -4,7 +4,6 @@ module Propellor.Attr where
|
||||||
|
|
||||||
import Propellor.Types
|
import Propellor.Types
|
||||||
import Propellor.Types.Attr
|
import Propellor.Types.Attr
|
||||||
import Propellor.Types.Dns
|
|
||||||
|
|
||||||
import "mtl" Control.Monad.Reader
|
import "mtl" Control.Monad.Reader
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
|
|
@ -1,8 +1,10 @@
|
||||||
module Propellor.Property.Dns (
|
module Propellor.Property.Dns (
|
||||||
module Propellor.Types.Dns,
|
module Propellor.Types.Dns,
|
||||||
|
primary,
|
||||||
secondary,
|
secondary,
|
||||||
servingZones,
|
servingZones,
|
||||||
mkSOA,
|
mkSOA,
|
||||||
|
rootAddressesFrom,
|
||||||
writeZoneFile,
|
writeZoneFile,
|
||||||
nextSerialNumber,
|
nextSerialNumber,
|
||||||
adjustSerialNumber,
|
adjustSerialNumber,
|
||||||
|
@ -22,6 +24,23 @@ import qualified Data.Map as M
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
||||||
|
-- | Primary dns server for a domain.
|
||||||
|
--
|
||||||
|
-- TODO: Does not yet add it to named.conf.local.
|
||||||
|
primary :: [Host] -> Domain -> SOA -> Property
|
||||||
|
primary hosts domain soa = withwarnings (check needupdate baseprop)
|
||||||
|
`requires` Apt.serviceInstalledRunning "bind9"
|
||||||
|
`onChange` Service.reloaded "bind9"
|
||||||
|
where
|
||||||
|
(zone, warnings) = genZone hosts domain soa
|
||||||
|
zonefile = "/etc/bind/propellor/db." ++ domain
|
||||||
|
needupdate = (/= Just zone) <$> readZonePropellorFile zonefile
|
||||||
|
baseprop = property ("dns primary for " ++ domain) $ makeChange $ do
|
||||||
|
writeZoneFile zone zonefile
|
||||||
|
withwarnings p = adjustProperty p $ \satisfy -> do
|
||||||
|
mapM_ warningMessage warnings
|
||||||
|
satisfy
|
||||||
|
|
||||||
namedconf :: FilePath
|
namedconf :: FilePath
|
||||||
namedconf = "/etc/bind/named.conf.local"
|
namedconf = "/etc/bind/named.conf.local"
|
||||||
|
|
||||||
|
@ -56,7 +75,7 @@ confStanza c =
|
||||||
(map (\ip -> "\t\t" ++ fromIPAddr ip ++ ";") (confMasters c)) ++
|
(map (\ip -> "\t\t" ++ fromIPAddr ip ++ ";") (confMasters c)) ++
|
||||||
[ "\t};" ]
|
[ "\t};" ]
|
||||||
|
|
||||||
-- | Rewrites the whole named.conf.local file to serve the specificed
|
-- | Rewrites the whole named.conf.local file to serve the specified
|
||||||
-- zones.
|
-- zones.
|
||||||
servingZones :: [NamedConf] -> Property
|
servingZones :: [NamedConf] -> Property
|
||||||
servingZones zs = hasContent namedconf (concatMap confStanza zs)
|
servingZones zs = hasContent namedconf (concatMap confStanza zs)
|
||||||
|
@ -66,6 +85,10 @@ servingZones zs = hasContent namedconf (concatMap confStanza zs)
|
||||||
|
|
||||||
-- | Generates a SOA with some fairly sane numbers in it.
|
-- | Generates a SOA with some fairly sane numbers in it.
|
||||||
--
|
--
|
||||||
|
-- The Domain is the domain to use in the SOA record. Typically
|
||||||
|
-- something like ns1.example.com. Not the domain that this is the SOA
|
||||||
|
-- record for.
|
||||||
|
--
|
||||||
-- The SerialNumber can be whatever serial number was used by the domain
|
-- The SerialNumber can be whatever serial number was used by the domain
|
||||||
-- before propellor started managing it. Or 0 if the domain has only ever
|
-- before propellor started managing it. Or 0 if the domain has only ever
|
||||||
-- been managed by propellor.
|
-- been managed by propellor.
|
||||||
|
@ -73,19 +96,22 @@ servingZones zs = hasContent namedconf (concatMap confStanza zs)
|
||||||
-- You do not need to increment the SerialNumber when making changes!
|
-- You do not need to increment the SerialNumber when making changes!
|
||||||
-- Propellor will automatically add the number of commits in the git
|
-- Propellor will automatically add the number of commits in the git
|
||||||
-- repository to the SerialNumber.
|
-- repository to the SerialNumber.
|
||||||
mkSOA :: Domain -> SerialNumber -> [Record] -> SOA
|
mkSOA :: Domain -> SerialNumber -> [Record] -> [Record] -> SOA
|
||||||
mkSOA d sn rs = SOA
|
mkSOA d sn rs1 rs2 = SOA
|
||||||
{ sDomain = AbsDomain d
|
{ sDomain = AbsDomain d
|
||||||
, sSerial = sn
|
, sSerial = sn
|
||||||
, sRefresh = hours 4
|
, sRefresh = hours 4
|
||||||
, sRetry = hours 1
|
, sRetry = hours 1
|
||||||
, sExpire = 2419200 -- 4 weeks
|
, sExpire = 2419200 -- 4 weeks
|
||||||
, sTTL = hours 8
|
, sTTL = hours 8
|
||||||
, sRecord = rs
|
, sRecord = rs1 ++ rs2
|
||||||
}
|
}
|
||||||
where
|
where
|
||||||
hours n = n * 60 * 60
|
hours n = n * 60 * 60
|
||||||
|
|
||||||
|
rootAddressesFrom :: [Host] -> HostName -> [Record]
|
||||||
|
rootAddressesFrom hosts hn = map Address (hostAddresses hn hosts)
|
||||||
|
|
||||||
dValue :: BindDomain -> String
|
dValue :: BindDomain -> String
|
||||||
dValue (RelDomain d) = d
|
dValue (RelDomain d) = d
|
||||||
dValue (AbsDomain d) = d ++ "."
|
dValue (AbsDomain d) = d ++ "."
|
||||||
|
@ -137,7 +163,8 @@ writeZoneFile z f = do
|
||||||
offset <- serialNumberOffset
|
offset <- serialNumberOffset
|
||||||
let z' = nextSerialNumber
|
let z' = nextSerialNumber
|
||||||
(adjustSerialNumber z (+ offset))
|
(adjustSerialNumber z (+ offset))
|
||||||
(succ oldserial)
|
oldserial
|
||||||
|
createDirectoryIfMissing True (takeDirectory f)
|
||||||
writeFile f (genZoneFile z')
|
writeFile f (genZoneFile z')
|
||||||
writeZonePropellorFile f z'
|
writeZonePropellorFile f z'
|
||||||
|
|
||||||
|
|
|
@ -21,6 +21,7 @@ module Propellor.Types
|
||||||
, GpgKeyId
|
, GpgKeyId
|
||||||
, SshKeyType(..)
|
, SshKeyType(..)
|
||||||
, module Propellor.Types.OS
|
, module Propellor.Types.OS
|
||||||
|
, module Propellor.Types.Dns
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
|
@ -31,6 +32,7 @@ import "MonadCatchIO-transformers" Control.Monad.CatchIO
|
||||||
|
|
||||||
import Propellor.Types.Attr
|
import Propellor.Types.Attr
|
||||||
import Propellor.Types.OS
|
import Propellor.Types.OS
|
||||||
|
import Propellor.Types.Dns
|
||||||
|
|
||||||
data Host = Host [Property] SetAttr
|
data Host = Host [Property] SetAttr
|
||||||
|
|
||||||
|
|
|
@ -40,6 +40,16 @@ hosts = -- (o) `
|
||||||
& ipv4 "162.248.143.249"
|
& ipv4 "162.248.143.249"
|
||||||
& ipv6 "2002:5044:5531::1"
|
& ipv6 "2002:5044:5531::1"
|
||||||
|
|
||||||
|
& Dns.primary hosts "olduse.net" $
|
||||||
|
Dns.mkSOA "ns1.kitenet.net" 100
|
||||||
|
(Dns.rootAddressesFrom hosts "branchable.com")
|
||||||
|
[ NS "ns1.kitenet.net"
|
||||||
|
, NS "ns6.gandi.net"
|
||||||
|
, NS "ns2.kitenet.net"
|
||||||
|
, MX 0 "kitenet.net"
|
||||||
|
, TXT "v=spf1 a -all"
|
||||||
|
]
|
||||||
|
|
||||||
& cleanCloudAtCost
|
& cleanCloudAtCost
|
||||||
& Apt.unattendedUpgrades
|
& Apt.unattendedUpgrades
|
||||||
& Network.ipv6to4
|
& Network.ipv6to4
|
||||||
|
@ -242,7 +252,7 @@ myDnsSecondary =
|
||||||
]
|
]
|
||||||
where
|
where
|
||||||
master = hostAddresses "wren.kitenet.net" hosts
|
master = hostAddresses "wren.kitenet.net" hosts
|
||||||
branchablemaster = hostAddresses "pell.branchable.com" hosts
|
branchablemaster = hostAddresses "branchable.com" hosts
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = defaultMain hosts
|
main = defaultMain hosts
|
||||||
|
@ -274,7 +284,11 @@ monsters = -- but do want to track their public keys etc.
|
||||||
& ipv4 "80.68.85.49"
|
& ipv4 "80.68.85.49"
|
||||||
& ipv6 "2001:41c8:125:49::10"
|
& ipv6 "2001:41c8:125:49::10"
|
||||||
& cname "kite.kitenet.net"
|
& cname "kite.kitenet.net"
|
||||||
, host "pell.branchable.com"
|
, host "branchable.com"
|
||||||
& ipv4 "66.228.46.55"
|
& ipv4 "66.228.46.55"
|
||||||
& ipv6 "2600:3c03::f03c:91ff:fedf:c0e5"
|
& ipv6 "2600:3c03::f03c:91ff:fedf:c0e5"
|
||||||
|
& cname "www.olduse.net"
|
||||||
|
& cname "git.olduse.net"
|
||||||
|
, host "virgil.koldfront.dk"
|
||||||
|
& cname "article.olduse.net"
|
||||||
]
|
]
|
||||||
|
|
Loading…
Reference in New Issue