propellor spin

This commit is contained in:
Joey Hess 2014-04-08 16:58:11 -04:00
parent 2e6f7c1b5d
commit 0460a04474
Failed to extract signature
4 changed files with 36 additions and 1 deletions

View File

@ -11,6 +11,13 @@ hasContent :: FilePath -> [Line] -> Property
f `hasContent` newcontent = fileProperty ("replace " ++ f) f `hasContent` newcontent = fileProperty ("replace " ++ f)
(\_oldcontent -> newcontent) f (\_oldcontent -> newcontent) f
-- | Ensures a file has contents that comes from PrivData.
-- Note: Does not do anything with the permissions of the file to prevent
-- it from being seen.
hasPrivContent :: FilePath -> Property
hasPrivContent f = Property ("privcontent " ++ f) $
withPrivData (PrivFile f) (\v -> ensureProperty $ f `hasContent` lines v)
-- | Ensures that a line is present in a file, adding it to the end if not. -- | Ensures that a line is present in a file, adding it to the end if not.
containsLine :: FilePath -> Line -> Property containsLine :: FilePath -> Line -> Property
f `containsLine` l = fileProperty (f ++ " contains:" ++ l) go f f `containsLine` l = fileProperty (f ++ " contains:" ++ l) go f

View File

@ -0,0 +1,15 @@
module Propellor.Property.OpenId where
import Propellor
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Apt as Apt
providerFor :: [UserName] -> Property
providerFor users = propertyList ("openid provider") $
[ serviceRunning "apache2"
`requires` Apt.installed ["apache2"]
, Apt.installed ["simpleid"]
] ++ map identfile users
where
identfile u = File.hasPrivContent $ concat
[ "/var/lib/simpleid/identities/", u, ".identity" ]

View File

@ -100,6 +100,7 @@ data PrivDataField
= DockerAuthentication = DockerAuthentication
| SshPrivKey UserName | SshPrivKey UserName
| Password UserName | Password UserName
| PrivFile FilePath
deriving (Read, Show, Ord, Eq) deriving (Read, Show, Ord, Eq)

View File

@ -12,6 +12,7 @@ import qualified Propellor.Property.User as User
import qualified Propellor.Property.Hostname as Hostname 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.OpenId as OpenId
import qualified Propellor.Property.Docker as Docker import qualified Propellor.Property.Docker as Docker
import qualified Propellor.Property.SiteSpecific.GitHome as GitHome import qualified Propellor.Property.SiteSpecific.GitHome as GitHome
import qualified Propellor.Property.SiteSpecific.GitAnnexBuilder as GitAnnexBuilder import qualified Propellor.Property.SiteSpecific.GitAnnexBuilder as GitAnnexBuilder
@ -35,6 +36,7 @@ host hostname@"clam.kitenet.net" = standardSystem Unstable $ props
& Apt.installed ["git-annex", "mtr"] & Apt.installed ["git-annex", "mtr"]
& Tor.isBridge & Tor.isBridge
& JoeySites.oldUseNetshellBox & JoeySites.oldUseNetshellBox
& Docker.docked container hostname "openid-provider"
& Docker.configured & Docker.configured
& Docker.garbageCollected & Docker.garbageCollected
-- Orca is the main git-annex build box. -- Orca is the main git-annex build box.
@ -59,7 +61,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 _host name container _parenthost name
-- Simple web server, publishing the outside host's /var/www
| name == "webserver" = Just $ Docker.containerFrom | name == "webserver" = Just $ Docker.containerFrom
(image $ System (Debian Unstable) "amd64") (image $ System (Debian Unstable) "amd64")
[ Docker.publish "8080:80" [ Docker.publish "8080:80"
@ -68,6 +71,14 @@ container _host name
& serviceRunning "apache2" & serviceRunning "apache2"
`requires` Apt.installed ["apache2"] `requires` Apt.installed ["apache2"]
] ]
-- My own openid provider. Uses php, so containerized for security
-- and administrative sanity.
| name == "openid-provider" = Just $ Docker.containerFrom
(image $ System (Debian Stable) "amd64")
[ Docker.publish "8081:80"
, Docker.inside $ props
& OpenId.providerFor ["joey", "liw"]
]
-- armel builder has a companion container that run amd64 and -- armel builder has a companion container that run amd64 and
-- runs the build first to get TH splices. They share a home -- runs the build first to get TH splices. They share a home
@ -96,6 +107,7 @@ container _host name
-- | Docker images I prefer to use. -- | Docker images I prefer to use.
image :: System -> Docker.Image image :: System -> Docker.Image
image (System (Debian Unstable) arch) = "joeyh/debian-unstable-" ++ arch image (System (Debian Unstable) arch) = "joeyh/debian-unstable-" ++ arch
image (System (Debian Stable) arch) = "joeyh/debian-stable-" ++ arch
image _ = "debian-stable-official" -- does not currently exist! image _ = "debian-stable-official" -- does not currently exist!
-- This is my standard system setup -- This is my standard system setup