various improvements

This commit is contained in:
Joey Hess 2014-04-01 16:58:11 -04:00
parent 6a82cdc41c
commit e6d24b49b8
9 changed files with 129 additions and 35 deletions

View File

@ -16,16 +16,14 @@ sourcesList = "/etc/apt/sources.list"
type Url = String type Url = String
type Section = String type Section = String
data Suite = Stable | Testing | Unstable | Experimental showSuite :: DebianSuite -> String
deriving Show
showSuite :: Suite -> String
showSuite Stable = "stable" showSuite Stable = "stable"
showSuite Testing = "testing" showSuite Testing = "testing"
showSuite Unstable = "unstable" showSuite Unstable = "unstable"
showSuite Experimental = "experimental" showSuite Experimental = "experimental"
showSuite (DebianRelease r) = r
debLine :: Suite -> Url -> [Section] -> Line debLine :: DebianSuite -> Url -> [Section] -> Line
debLine suite mirror sections = unwords $ debLine suite mirror sections = unwords $
["deb", mirror, showSuite suite] ++ sections ["deb", mirror, showSuite suite] ++ sections
@ -37,14 +35,14 @@ srcLine l = case words l of
stdSections :: [Section] stdSections :: [Section]
stdSections = ["main", "contrib", "non-free"] stdSections = ["main", "contrib", "non-free"]
debCdn :: Suite -> [Line] debCdn :: DebianSuite -> [Line]
debCdn suite = [l, srcLine l] debCdn suite = [l, srcLine l]
where where
l = debLine suite "http://cdn.debian.net/debian" stdSections l = debLine suite "http://cdn.debian.net/debian" stdSections
{- | Makes sources.list have a standard content using the mirror CDN, {- | Makes sources.list have a standard content using the mirror CDN,
- with a particular Suite. -} - with a particular DebianSuite. -}
stdSourcesList :: Suite -> Property stdSourcesList :: DebianSuite -> Property
stdSourcesList suite = setSourcesList (debCdn suite) stdSourcesList suite = setSourcesList (debCdn suite)
`describe` ("standard sources.list for " ++ show suite) `describe` ("standard sources.list for " ++ show suite)
@ -81,6 +79,12 @@ removed ps = check (or <$> isInstalled' ps) go
where where
go = runApt $ ["-y", "remove"] ++ ps go = runApt $ ["-y", "remove"] ++ ps
buildDep :: [Package] -> Property
buildDep ps = check (isInstallable ps) go
`describe` (unwords $ "apt build-dep":ps)
where
go = runApt $ ["-y", "build-dep"] ++ ps
isInstallable :: [Package] -> IO Bool isInstallable :: [Package] -> IO Bool
isInstallable ps = do isInstallable ps = do
l <- isInstalled' ps l <- isInstalled' ps

View File

@ -2,6 +2,7 @@ module Propellor.Property.Cmd (
cmdProperty, cmdProperty,
cmdProperty', cmdProperty',
scriptProperty, scriptProperty,
userScriptProperty,
serviceRunning, serviceRunning,
) where ) where
@ -39,6 +40,13 @@ scriptProperty script = cmdProperty "sh" ["-c", shellcmd]
where where
shellcmd = intercalate " ; " ("set -e" : script) shellcmd = intercalate " ; " ("set -e" : script)
-- | A property that can satisfied by running a series of shell commands,
-- as user (staring in their home directory).
userScriptProperty :: UserName -> [String] -> Property
userScriptProperty user script = cmdProperty "su" ["-c", shellcmd, user]
where
shellcmd = intercalate " ; " ("set -e" : "cd" : script)
-- | Ensures that a service is running. -- | Ensures that a service is running.
-- --
-- Note that due to the general poor state of init scripts, the best -- Note that due to the general poor state of init scripts, the best

View File

@ -99,12 +99,12 @@ containerDesc cid p = p `describe` desc
-- | Ensures that a docker container is set up and running. The container -- | Ensures that a docker container is set up and running. The container
-- has its own Properties which are handled by running propellor -- has its own Properties which are handled by running propellor
-- inside the container. -- inside the container.
hasContainer docked
:: HostName :: (HostName -> ContainerName -> Maybe (Container))
-> HostName
-> ContainerName -> ContainerName
-> (HostName -> ContainerName -> Maybe (Container))
-> Property -> Property
hasContainer hn cn findcontainer = docked findcontainer hn cn =
case findcontainer hn cn of case findcontainer hn cn of
Nothing -> containerDesc cid $ Property "" $ do Nothing -> containerDesc cid $ Property "" $ do
warningMessage $ "missing definition for docker container \"" ++ fromContainerId cid warningMessage $ "missing definition for docker container \"" ++ fromContainerId cid

View File

@ -0,0 +1,45 @@
module Propellor.Property.SiteSpecific.GitAnnexBuilder where
import Propellor
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.User as User
import Propellor.Property.Cron (CronTimes)
type Arch = String
builduser :: UserName
builduser = "builder"
builddir :: FilePath
builddir = "gitbuilder"
builder :: Arch -> CronTimes -> Property
builder arch crontimes = combineProperties
[ Apt.buildDep ["git-annex"]
, Apt.installed ["git", "rsync", "liblockfile-simple-perl"]
, serviceRunning "cron" `requires` Apt.installed ["cron"]
, User.accountFor builduser
, check (not <$> hasbuilddir) $ userScriptProperty builduser
[ "cabal update"
, "git clone https://github.com/joeyh/gitbuilder/"
, "cd gitbuilder && git checkout " ++ arch
, "echo '"++crontimes++" cd gitbuilder/autobuild' | crontab -"
]
`describe` "gitbuilder setup"
-- The builduser account does not have a password set,
-- instead use the password privdata to hold the rsync server
-- password used to upload the built image.
, Property "rsync password" $ do
d <- homedir
let f = d </> "rsyncpassword"
withPrivData (Password builduser) $ \p -> do
oldp <- catchDefaultIO "" $ readFileStrict f
if p /= oldp
then makeChange $ writeFile f p
else noChange
]
where
homedir = fromMaybe ("/home/" ++ builduser) <$> User.homedir builduser
hasbuilddir = do
d <- homedir
doesDirectoryExist (d </> builddir)

View File

@ -1,11 +1,11 @@
module Propellor.Property.GitHome where module Propellor.Property.SiteSpecific.GitHome where
import Propellor import Propellor
import qualified Propellor.Property.Apt as Apt import qualified Propellor.Property.Apt as Apt
import Propellor.Property.User import Propellor.Property.User
import Utility.SafeCommand import Utility.SafeCommand
{- | Clones Joey Hess's git home directory, and runs its fixups script. -} -- | Clones Joey Hess's git home directory, and runs its fixups script.
installedFor :: UserName -> Property installedFor :: UserName -> Property
installedFor user = check (not <$> hasGitDir user) $ installedFor user = check (not <$> hasGitDir user) $
Property ("githome " ++ user) (go =<< homedir user) Property ("githome " ++ user) (go =<< homedir user)
@ -14,15 +14,20 @@ installedFor user = check (not <$> hasGitDir user) $
go Nothing = noChange go Nothing = noChange
go (Just home) = do go (Just home) = do
let tmpdir = home </> "githome" let tmpdir = home </> "githome"
ok <- boolSystem "git" [Param "clone", Param url, Param tmpdir] ensureProperty $ combineProperties
<&&> (and <$> moveout tmpdir home) [ userScriptProperty user ["git clone " ++ url ++ " " ++ tmpdir]
<&&> (catchBoolIO $ removeDirectory tmpdir >> return True) , Property "moveout" $ makeChange $ void $
<&&> boolSystem "su" [Param "-c", Param "cd; rm -rf .aptitude/ .bashrc .profile; mr checkout; bin/fixups", Param user] moveout tmpdir home
return $ if ok then MadeChange else FailedChange , Property "rmdir" $ makeChange $ void $
catchMaybeIO $ removeDirectory tmpdir
, userScriptProperty user ["rm -rf .aptitude/ .bashrc .profile; mr checkout; bin/fixups"]
]
moveout tmpdir home = do moveout tmpdir home = do
fs <- dirContents tmpdir fs <- dirContents tmpdir
forM fs $ \f -> boolSystem "mv" [File f, File home] forM fs $ \f -> boolSystem "mv" [File f, File home]
url = "git://git.kitenet.net/joey/home"
url :: String
url = "git://git.kitenet.net/joey/home"
hasGitDir :: UserName -> IO Bool hasGitDir :: UserName -> IO Bool
hasGitDir user = go =<< homedir user hasGitDir user = go =<< homedir user

View File

@ -1,7 +1,7 @@
-- | Specific configuation for Joey Hess's sites. Probably not useful to -- | Specific configuation for Joey Hess's sites. Probably not useful to
-- others except as an example. -- others except as an example.
module Propellor.Property.JoeySites where module Propellor.Property.SiteSpecific.JoeySites where
import Propellor import Propellor
import qualified Propellor.Property.Apt as Apt import qualified Propellor.Property.Apt as Apt

View File

@ -6,15 +6,15 @@ import Propellor
data Eep = YesReallyDeleteHome data Eep = YesReallyDeleteHome
sshAccountFor :: UserName -> Property accountFor :: UserName -> Property
sshAccountFor user = check (isNothing <$> homedir user) $ cmdProperty "adduser" accountFor user = check (isNothing <$> homedir user) $ cmdProperty "adduser"
[ "--disabled-password" [ "--disabled-password"
, "--gecos", "" , "--gecos", ""
, user , user
] ]
`describe` ("ssh account " ++ user) `describe` ("ssh account " ++ user)
{- | Removes user home directory!! Use with caution. -} -- | Removes user home directory!! Use with caution.
nuked :: UserName -> Eep -> Property nuked :: UserName -> Eep -> Property
nuked user _ = check (isJust <$> homedir user) $ cmdProperty "userdel" nuked user _ = check (isJust <$> homedir user) $ cmdProperty "userdel"
[ "-r" [ "-r"
@ -22,8 +22,8 @@ nuked user _ = check (isJust <$> homedir user) $ cmdProperty "userdel"
] ]
`describe` ("nuked user " ++ user) `describe` ("nuked user " ++ user)
{- | Only ensures that the user has some password set. It may or may -- | Only ensures that the user has some password set. It may or may
- not be the password from the PrivData. -} -- not be the password from the PrivData.
hasSomePassword :: UserName -> Property hasSomePassword :: UserName -> Property
hasSomePassword user = check ((/= HasPassword) <$> getPasswordStatus user) $ hasSomePassword user = check ((/= HasPassword) <$> getPasswordStatus user) $
hasPassword user hasPassword user

View File

@ -26,6 +26,24 @@ instance Monoid Result where
mappend _ MadeChange = MadeChange mappend _ MadeChange = MadeChange
mappend NoChange NoChange = NoChange mappend NoChange NoChange = NoChange
-- | High level descritption of a operating system.
data System = System Distribution Architecture
deriving (Show)
data Distribution
= Debian DebianSuite
| Ubuntu Release
deriving (Show)
data DebianSuite = Experimental | Unstable | Testing | Stable | DebianRelease Release
deriving (Show)
type Release = String
data Architecture = Amd64 | I386 | Armel
deriving (Show)
-- | Results of actions, with color.
class ActionResult a where class ActionResult a where
getActionResult :: a -> (String, ColorIntensity, Color) getActionResult :: a -> (String, ColorIntensity, Color)

View File

@ -14,8 +14,9 @@ import qualified Propellor.Property.Hostname as Hostname
import qualified Propellor.Property.Reboot as Reboot import qualified Propellor.Property.Reboot as Reboot
import qualified Propellor.Property.Tor as Tor import qualified Propellor.Property.Tor as Tor
import qualified Propellor.Property.Docker as Docker import qualified Propellor.Property.Docker as Docker
import qualified Propellor.Property.GitHome as GitHome import qualified Propellor.Property.SiteSpecific.GitHome as GitHome
import qualified Propellor.Property.JoeySites as JoeySites import qualified Propellor.Property.SiteSpecific.GitAnnexBuilder as GitAnnexBuilder
import qualified Propellor.Property.SiteSpecific.JoeySites as JoeySites
main :: IO () main :: IO ()
main = defaultMain [host, Docker.containerProperties container] main = defaultMain [host, Docker.containerProperties container]
@ -28,7 +29,7 @@ main = defaultMain [host, Docker.containerProperties container]
host :: HostName -> Maybe [Property] host :: HostName -> Maybe [Property]
host hostname@"clam.kitenet.net" = Just host hostname@"clam.kitenet.net" = Just
[ cleanCloudAtCost hostname [ cleanCloudAtCost hostname
, standardSystem Apt.Unstable , standardSystem Unstable
, Apt.unattendedUpgrades True , Apt.unattendedUpgrades True
, Network.ipv6to4 , Network.ipv6to4
-- Clam is a tor bridge, and an olduse.net shellbox and other -- Clam is a tor bridge, and an olduse.net shellbox and other
@ -37,15 +38,16 @@ host hostname@"clam.kitenet.net" = Just
, JoeySites.oldUseNetshellBox , JoeySites.oldUseNetshellBox
, Docker.configured , Docker.configured
, File.dirExists "/var/www" , File.dirExists "/var/www"
, Docker.hasContainer hostname "webserver" container , Docker.docked container hostname "webserver"
, Apt.installed ["git-annex", "mtr"] , Apt.installed ["git-annex", "mtr"]
-- Should come last as it reboots. -- Should come last as it reboots.
, Apt.installed ["systemd-sysv"] `onChange` Reboot.now , Apt.installed ["systemd-sysv"] `onChange` Reboot.now
] ]
host "orca.kitenet.net" = Just host hostname@"orca.kitenet.net" = Just
[ standardSystem Apt.Unstable [ standardSystem Unstable
, Apt.unattendedUpgrades True , Apt.unattendedUpgrades True
, Docker.configured , Docker.configured
, Docker.docked container hostname "git-annex-amd64-builder"
] ]
-- add more hosts here... -- add more hosts here...
--host "foo.example.com" = --host "foo.example.com" =
@ -54,7 +56,8 @@ host _ = Nothing
-- | This is where Docker containers are set up. A container -- | This is where Docker containers are set up. A container
-- can vary by hostname where it's used, or be the same everywhere. -- can vary by hostname where it's used, or be the same everywhere.
container :: HostName -> Docker.ContainerName -> Maybe (Docker.Container) container :: HostName -> Docker.ContainerName -> Maybe (Docker.Container)
container _ "webserver" = Just $ Docker.containerFrom "joeyh/debian-unstable" container _ "webserver" = Just $ Docker.containerFrom
(image $ System (Debian Unstable) Amd64)
[ Docker.publish "8080:80" [ Docker.publish "8080:80"
, Docker.volume "/var/www:/var/www" , Docker.volume "/var/www:/var/www"
, Docker.inside , Docker.inside
@ -62,10 +65,21 @@ container _ "webserver" = Just $ Docker.containerFrom "joeyh/debian-unstable"
`requires` Apt.installed ["apache2"] `requires` Apt.installed ["apache2"]
] ]
] ]
container _ "git-annex-amd64-builder" = Just $ Docker.containerFrom
(image $ System (Debian Unstable) Amd64)
[ Docker.inside [ GitAnnexBuilder.builder "amd64" "30 * * * *" ] ]
container _ _ = Nothing container _ _ = Nothing
-- | Docker images I prefer to use.
-- Edit as suites you, or delete this function and just put the image names
-- above.
image :: System -> Docker.Image
image (System (Debian Unstable) Amd64) = "joeyh/debian-unstable"
image (System (Debian Unstable) I386) = "joeyh/debian-i386"
image _ = "debian"
-- This is my standard system setup -- This is my standard system setup
standardSystem :: Apt.Suite -> Property standardSystem :: DebianSuite -> Property
standardSystem suite = propertyList "standard system" standardSystem suite = propertyList "standard system"
[ Apt.stdSourcesList suite `onChange` Apt.upgrade [ Apt.stdSourcesList suite `onChange` Apt.upgrade
, Apt.installed ["etckeeper"] , Apt.installed ["etckeeper"]
@ -76,7 +90,7 @@ standardSystem suite = propertyList "standard system"
-- is safely in place. -- is safely in place.
, check (Ssh.hasAuthorizedKeys "root") $ , check (Ssh.hasAuthorizedKeys "root") $
Ssh.passwordAuthentication False Ssh.passwordAuthentication False
, User.sshAccountFor "joey" , User.accountFor "joey"
, User.hasSomePassword "joey" , User.hasSomePassword "joey"
, Sudo.enabledFor "joey" , Sudo.enabledFor "joey"
, GitHome.installedFor "joey" , GitHome.installedFor "joey"