-- | Specific configuration for Joey Hess's sites. Probably not useful to
-- others except as an example.

{-# LANGUAGE FlexibleContexts, TypeFamilies #-}

module Propellor.Property.SiteSpecific.JoeySites where

import Propellor.Base
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.File as File
import qualified Propellor.Property.ConfFile as ConfFile
import qualified Propellor.Property.Gpg as Gpg
import qualified Propellor.Property.Ssh as Ssh
import qualified Propellor.Property.Git as Git
import qualified Propellor.Property.Cron as Cron
import qualified Propellor.Property.Service as Service
import qualified Propellor.Property.User as User
import qualified Propellor.Property.Group as Group
import qualified Propellor.Property.Sudo as Sudo
import qualified Propellor.Property.Borg as Borg
import qualified Propellor.Property.Apache as Apache
import qualified Propellor.Property.Postfix as Postfix
import qualified Propellor.Property.Systemd as Systemd
import qualified Propellor.Property.Network as Network
import qualified Propellor.Property.Fail2Ban as Fail2Ban
import qualified Propellor.Property.LetsEncrypt as LetsEncrypt
import qualified Propellor.Property.Mount as Mount
import Utility.Split

import Data.List
import System.Posix.Files

scrollBox :: Property (HasInfo + DebianLike)
scrollBox :: Property (HasInfo + DebianLike)
scrollBox = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"scroll server" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Property DebianLike
User.accountFor (Desc -> User
User Desc
"scroll")
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Desc -> Desc -> Maybe Desc -> Property DebianLike
Git.cloned (Desc -> User
User Desc
"scroll") Desc
"git://git.kitenet.net/scroll" (Desc
d Desc -> Desc -> Desc
</> Desc
"scroll") Maybe Desc
forall a. Maybe a
Nothing
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"ghc", Desc
"make", Desc
"cabal-install", Desc
"libghc-vector-dev",
		Desc
"libghc-bytestring-dev", Desc
"libghc-mtl-dev", Desc
"libghc-ncurses-dev",
		Desc
"libghc-random-dev", Desc
"libghc-monad-loops-dev", Desc
"libghc-text-dev",
		Desc
"libghc-ifelse-dev", Desc
"libghc-case-insensitive-dev",
		Desc
"libghc-data-default-dev", Desc
"libghc-optparse-applicative-dev"]
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> [Desc] -> UncheckedProperty UnixLike
userScriptProperty (Desc -> User
User Desc
"scroll")
		[ Desc
"cd " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d Desc -> Desc -> Desc
</> Desc
"scroll"
		, Desc
"git pull"
		, Desc
"cabal configure"
		, Desc
"make"
		]
		UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
s Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"#!/bin/sh"
		, Desc
"set -e"
		, Desc
"echo Preparing to run scroll!"
		, Desc
"cd " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d
		, Desc
"mkdir -p tmp"
		, Desc
"TMPDIR= t=$(tempfile -d tmp)"
		, Desc
"export t"
		, Desc
"rm -f \"$t\""
		, Desc
"mkdir \"$t\""
		, Desc
"cd \"$t\""
		, Desc
"echo"
		, Desc
"echo Note that games on this server are time-limited to 2 hours"
		, Desc
"echo 'Need more time? Run scroll locally instead!'"
		, Desc
"echo"
		, Desc
"echo Press Enter to start the game."
		, Desc
"read me"
		, Desc
"SHELL=/bin/sh script --timing=timing -c " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
g
		] Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` (Desc
s Desc -> FileMode -> Property UnixLike
`File.mode` ([FileMode] -> FileMode
combineModes (FileMode
ownerWriteModeFileMode -> [FileMode] -> [FileMode]
forall a. a -> [a] -> [a]
:[FileMode]
readModes [FileMode] -> [FileMode] -> [FileMode]
forall a. [a] -> [a] -> [a]
++ [FileMode]
executeModes)))
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
g Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"#!/bin/sh"
		, Desc
"if ! timeout --kill-after 1m --foreground 2h ../../scroll/scroll; then"
		, Desc
"echo Scroll seems to have ended unexpectedly. Possibly a bug.."
		, Desc
"else"
		, Desc
"echo Thanks for playing scroll! https://joeyh.name/code/scroll/"
		, Desc
"fi"
		, Desc
"echo Your game was recorded, as ID:$(basename \"$t\")"
		, Desc
"echo if you would like to talk about how it went, email scroll@joeyh.name"
		, Desc
"read line"
		] Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` (Desc
g Desc -> FileMode -> Property UnixLike
`File.mode` ([FileMode] -> FileMode
combineModes (FileMode
ownerWriteModeFileMode -> [FileMode] -> [FileMode]
forall a. a -> [a] -> [a]
:[FileMode]
readModes [FileMode] -> [FileMode] -> [FileMode]
forall a. [a] -> [a] -> [a]
++ [FileMode]
executeModes)))
	-- prevent port forwarding etc by not letting scroll log in via ssh
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
Ssh.sshdConfig Desc -> Desc -> Property UnixLike
`File.containsLine` (Desc
"DenyUsers scroll")
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Ssh.restarted
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Desc -> Property DebianLike
User.shellSetTo (Desc -> User
User Desc
"scroll") Desc
s
	Props DebianLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Property (HasInfo + DebianLike)
User.hasPassword (Desc -> User
User Desc
"scroll")
	-- telnetd attracted password crackers, so disabled
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.removed [Desc
"telnetd"]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"shellinabox"]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
"/etc/default/shellinabox"
		[ Desc
"# Deployed by propellor"
		, Desc
"SHELLINABOX_DAEMON_START=1"
		, Desc
"SHELLINABOX_PORT=4242"
		, Desc
"SHELLINABOX_ARGS=\"--disable-ssl --no-beep --service=:scroll:scroll:" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
":" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
s Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"\""
		]
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"shellinabox"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Service.running Desc
"shellinabox"
  where
	d :: Desc
d = Desc
"/home/scroll"
	s :: Desc
s = Desc
d Desc -> Desc -> Desc
</> Desc
"login.sh"
	g :: Desc
g = Desc
d Desc -> Desc -> Desc
</> Desc
"game.sh"

kgbServer :: Property (HasInfo + DebianLike)
kgbServer :: Property (HasInfo + DebianLike)
kgbServer = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
desc (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"kgb-bot"
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/default/kgb-bot" Desc -> Desc -> Property UnixLike
`File.containsLine` Desc
"BOT_ENABLED=1"
		Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"kgb bot enabled"
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.running Desc
"kgb-bot"
	Props DebianLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContent Desc
"/etc/kgb-bot/kgb.conf" Context
anyContext
		Property
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property DebianLike
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"kgb-bot"
  where
	desc :: Desc
desc = Desc
"kgb.kitenet.net setup"

-- git.kitenet.net and git.joeyh.name
gitServer :: [Host] -> Property (HasInfo + DebianLike)
gitServer :: [Host] -> Property (HasInfo + DebianLike)
gitServer [Host]
hosts = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"git.kitenet.net setup" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> BorgRepo
-> Times
-> [Desc]
-> [KeepPolicy]
-> Property DebianLike
Borg.backup Desc
"/srv/git" BorgRepo
borgrepo
		(Desc -> Times
Cron.Times Desc
"33 3 * * *")
		[]
		[Int -> KeepPolicy
Borg.KeepDays Int
30]
		Property DebianLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> CombinedType
     (Property DebianLike)
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Maybe Desc
-> User
-> Context
-> (SshKeyType, Desc)
-> Property (HasInfo + UnixLike)
forall c.
IsContext c =>
Maybe Desc
-> User -> c -> (SshKeyType, Desc) -> Property (HasInfo + UnixLike)
Ssh.userKeyAt (Desc -> Maybe Desc
forall a. a -> Maybe a
Just Desc
sshkey)
			(Desc -> User
User Desc
"root")
			(Desc -> Context
Context Desc
"git.kitenet.net")
			(SshKeyType
SshEd25519, Desc
"ssh-ed25519 AAAAC3NzaC1lZDI1NTE5AAAAIOvgBVYP6srImGbJ+kg1K68HeUQqxHEBQswMWSqu9WOu root@kite")
		Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> CombinedType
     (Property
        (MetaTypes
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
     (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Host] -> Desc -> User -> Property UnixLike
Ssh.knownHost [Host]
hosts Desc
"usw-s002.rsync.net" (Desc -> User
User Desc
"root")
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => User -> c -> Property (HasInfo + UnixLike)
Ssh.authorizedKeys (Desc -> User
User Desc
"family") (Desc -> Context
Context Desc
"git.kitenet.net")
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Property DebianLike
User.accountFor (Desc -> User
User Desc
"family")
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"git", Desc
"rsync", Desc
"cgit"]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"git-annex"]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"kgb-client"]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContentExposed Desc
"/etc/kgb-bot/kgb-client.conf" Context
anyContext
		Property
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property UnixLike
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> Property UnixLike
File.dirExists Desc
"/etc/kgb-bot/"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> RevertableProperty DebianLike DebianLike
Git.daemonRunning Desc
"/srv/git"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/cgitrc" Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"clone-url=https://git.joeyh.name/git/$CGIT_REPO_URL git://git.joeyh.name/$CGIT_REPO_URL"
		, Desc
"css=/cgit-css/cgit.css"
		, Desc
"logo=/cgit-css/cgit.png"
		, Desc
"enable-http-clone=1"
		, Desc
"root-title=Joey's git repositories"
		, Desc
"root-desc="
		, Desc
"enable-index-owner=0"
		, Desc
"snapshots=tar.gz"
		, Desc
"enable-git-config=1"
		, Desc
"scan-path=/srv/git"
		]
		Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"cgit configured"
	-- I keep the website used for git.kitenet.net/git.joeyh.name checked into git..
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Desc -> Desc -> Maybe Desc -> Property DebianLike
Git.cloned (Desc -> User
User Desc
"joey") Desc
"/srv/git/joey/git.kitenet.net.git" Desc
"/srv/web/git.kitenet.net" Maybe Desc
forall a. Maybe a
Nothing
	-- Don't need global apache configuration for cgit.
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a k (x :: [a]) (z :: [a]) (y :: k).
CheckCombinableNote x z (NoteFor ('Text "!")) =>
Props (MetaTypes x)
-> RevertableProperty (MetaTypes y) (MetaTypes z)
-> Props (MetaTypes (Combine x z))
! Desc -> RevertableProperty DebianLike DebianLike
Apache.confEnabled Desc
"cgit"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> RevertableProperty DebianLike DebianLike
website Desc
"git.kitenet.net"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> RevertableProperty DebianLike DebianLike
website Desc
"git.joeyh.name"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> RevertableProperty DebianLike DebianLike
Apache.modEnabled Desc
"cgi"
  where
	sshkey :: Desc
sshkey = Desc
"/root/.ssh/git.kitenet.net.key"
	borgrepo :: BorgRepo
borgrepo = Desc -> [BorgRepoOpt] -> BorgRepo
rsyncNetBorgRepo Desc
"git.kitenet.net.borg" [Desc -> BorgRepoOpt
Borg.UseSshKey Desc
sshkey]
	website :: Desc -> RevertableProperty DebianLike DebianLike
website Desc
hn = Desc
-> Desc
-> AgreeTOS
-> [Desc]
-> RevertableProperty DebianLike DebianLike
Apache.httpsVirtualHost' Desc
hn Desc
"/srv/web/git.kitenet.net/" AgreeTOS
letos
		[ Desc
Apache.iconDir
		, Desc
"  <Directory /srv/web/git.kitenet.net/>"
		, Desc
"    Options Indexes ExecCGI FollowSymlinks"
		, Desc
"    AllowOverride None"
		, Desc
"    AddHandler cgi-script .cgi"
		, Desc
"    DirectoryIndex index.cgi"
		,      Desc
Apache.allowAll
		, Desc
"  </Directory>"
		, Desc
""
		, Desc
"  ScriptAlias /cgi-bin/ /usr/lib/cgi-bin/"
		, Desc
"  <Directory /usr/lib/cgi-bin>"
		, Desc
"    SetHandler cgi-script"
		, Desc
"    Options ExecCGI"
		, Desc
"  </Directory>"
		]

type AnnexUUID = String

-- | A website, with files coming from a git-annex repository.
annexWebSite :: Git.RepoUrl -> HostName -> AnnexUUID -> [(String, Git.RepoUrl)] -> Property (HasInfo + DebianLike)
annexWebSite :: Desc
-> Desc
-> Desc
-> [(Desc, Desc)]
-> Property (HasInfo + DebianLike)
annexWebSite Desc
origin Desc
hn Desc
uuid [(Desc, Desc)]
remotes = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList (Desc
hn Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++Desc
" website using git-annex") (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Desc -> Desc -> Maybe Desc -> Property DebianLike
Git.cloned (Desc -> User
User Desc
"joey") Desc
origin Desc
dir Maybe Desc
forall a. Maybe a
Nothing
		Property DebianLike
-> Property UnixLike
-> CombinedType (Property DebianLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property UnixLike
setup
	Props DebianLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
hn
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
postupdatehook Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"#!/bin/sh"
		, Desc
"exec git update-server-info"
		] Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange`
			(Desc
postupdatehook Desc -> FileMode -> Property UnixLike
`File.mode` ([FileMode] -> FileMode
combineModes (FileMode
ownerWriteModeFileMode -> [FileMode] -> [FileMode]
forall a. a -> [a] -> [a]
:[FileMode]
readModes [FileMode] -> [FileMode] -> [FileMode]
forall a. [a] -> [a] -> [a]
++ [FileMode]
executeModes)))
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& RevertableProperty DebianLike DebianLike
setupapache
  where
	dir :: Desc
dir = Desc
"/srv/web/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
hn
	postupdatehook :: Desc
postupdatehook = Desc
dir Desc -> Desc -> Desc
</> Desc
".git/hooks/post-update"
	setup :: Property UnixLike
setup = User -> [Desc] -> UncheckedProperty UnixLike
userScriptProperty (Desc -> User
User Desc
"joey") [Desc]
setupscript
		UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
	setupscript :: [Desc]
setupscript =
		[ Desc
"cd " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc -> Desc
shellEscape Desc
dir
		, Desc
"git annex reinit " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc -> Desc
shellEscape Desc
uuid
		] [Desc] -> [Desc] -> [Desc]
forall a. [a] -> [a] -> [a]
++ ((Desc, Desc) -> Desc) -> [(Desc, Desc)] -> [Desc]
forall a b. (a -> b) -> [a] -> [b]
map (Desc, Desc) -> Desc
addremote [(Desc, Desc)]
remotes [Desc] -> [Desc] -> [Desc]
forall a. [a] -> [a] -> [a]
++
		[ Desc
"git annex get"
		, Desc
"git update-server-info"
		]
	addremote :: (Desc, Desc) -> Desc
addremote (Desc
name, Desc
url) = Desc
"git remote add " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc -> Desc
shellEscape Desc
name Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
" " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc -> Desc
shellEscape Desc
url
	setupapache :: RevertableProperty DebianLike DebianLike
setupapache = Desc
-> Desc
-> AgreeTOS
-> [Desc]
-> RevertableProperty DebianLike DebianLike
Apache.httpsVirtualHost' Desc
hn Desc
dir AgreeTOS
letos
		[ Desc
"  ServerAlias www."Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++Desc
hn
		,    Desc
Apache.iconDir
		, Desc
"  <Directory "Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++Desc
dirDesc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++Desc
">"
		, Desc
"    Options Indexes FollowSymLinks ExecCGI"
		, Desc
"    AllowOverride None"
		, Desc
"    AddHandler cgi-script .cgi"
		, Desc
"    DirectoryIndex index.html index.cgi"
		,      Desc
Apache.allowAll
		, Desc
"  </Directory>"
		]

letos :: LetsEncrypt.AgreeTOS
letos :: AgreeTOS
letos = Maybe Desc -> AgreeTOS
LetsEncrypt.AgreeTOS (Desc -> Maybe Desc
forall a. a -> Maybe a
Just Desc
"id@joeyh.name")

apacheSite :: HostName -> Apache.ConfigFile -> RevertableProperty DebianLike DebianLike
apacheSite :: Desc -> [Desc] -> RevertableProperty DebianLike DebianLike
apacheSite Desc
hn [Desc]
middle = Desc -> [Desc] -> RevertableProperty DebianLike DebianLike
Apache.siteEnabled Desc
hn ([Desc] -> RevertableProperty DebianLike DebianLike)
-> [Desc] -> RevertableProperty DebianLike DebianLike
forall a b. (a -> b) -> a -> b
$ Desc -> [Desc] -> [Desc]
apachecfg Desc
hn [Desc]
middle

apachecfg :: HostName -> Apache.ConfigFile -> Apache.ConfigFile
apachecfg :: Desc -> [Desc] -> [Desc]
apachecfg Desc
hn [Desc]
middle =
	[ Desc
"<VirtualHost *:" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Port -> Desc
forall t. ConfigurableValue t => t -> Desc
val Port
port Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
">"
	, Desc
"  ServerAdmin grue@joeyh.name"
	, Desc
"  ServerName "Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++Desc
hnDesc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++Desc
":" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Port -> Desc
forall t. ConfigurableValue t => t -> Desc
val Port
port
	]
	[Desc] -> [Desc] -> [Desc]
forall a. [a] -> [a] -> [a]
++ [Desc]
middle [Desc] -> [Desc] -> [Desc]
forall a. [a] -> [a] -> [a]
++
	[ Desc
""
	, Desc
"  ErrorLog /var/log/apache2/error.log"
	, Desc
"  LogLevel warn"
	, Desc
"  CustomLog /var/log/apache2/access.log combined"
	, Desc
"  ServerSignature On"
	, Desc
"  "
	, Desc
Apache.iconDir
	, Desc
"</VirtualHost>"
	]
	  where
		port :: Port
port = Int -> Port
Port Int
80

gitAnnexDistributor :: Property (HasInfo + DebianLike)
gitAnnexDistributor :: Property (HasInfo + DebianLike)
gitAnnexDistributor = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties Desc
"git-annex distributor, including rsync server and signer" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"rsync"]
	Props DebianLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContent Desc
"/etc/rsyncd.conf" (Desc -> Context
Context Desc
"git-annex distributor")
		Property
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property DebianLike
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"rsync"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContent Desc
"/etc/rsyncd.secrets" (Desc -> Context
Context Desc
"git-annex distributor")
		Property
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property DebianLike
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"rsync"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/default/rsync" Desc -> Desc -> Property UnixLike
`File.containsLine` Desc
"RSYNC_ENABLE=true"
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.running Desc
"rsync"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.enabled Desc
"rsync"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property UnixLike
endpoint Desc
"/srv/web/downloads.kitenet.net/git-annex/autobuild"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property UnixLike
endpoint Desc
"/srv/web/downloads.kitenet.net/git-annex/autobuild/x86_64-apple-yosemite"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property UnixLike
endpoint Desc
"/srv/web/downloads.kitenet.net/git-annex/autobuild/windows"
	-- git-annex distribution signing key
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& GpgKeyId -> User -> Property (HasInfo + DebianLike)
Gpg.keyImported (Desc -> GpgKeyId
Gpg.GpgKeyId Desc
"89C809CB") (Desc -> User
User Desc
"joey")
	-- used for building rpms
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"rpm", Desc
"createrepo-c"]
  where
	endpoint :: Desc -> Property UnixLike
endpoint Desc
d = Desc -> Props UnixLike -> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties (Desc
"endpoint " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d) (Props UnixLike -> Property UnixLike)
-> Props UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		Props UnixLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property UnixLike
File.dirExists Desc
d
		Props UnixLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> User -> Group -> Property UnixLike
File.ownerGroup Desc
d (Desc -> User
User Desc
"joey") (Desc -> Group
Group Desc
"joey")

downloads :: Property (HasInfo + DebianLike)
downloads :: Property (HasInfo + DebianLike)
downloads = Desc
-> Desc
-> Desc
-> [(Desc, Desc)]
-> Property (HasInfo + DebianLike)
annexWebSite Desc
"/srv/git/downloads.git"
	Desc
"downloads.kitenet.net"
	Desc
"840760dc-08f0-11e2-8c61-576b7e66acfd"
	[]

tmp :: Property (HasInfo + DebianLike)
tmp :: Property (HasInfo + DebianLike)
tmp = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"tmp.joeyh.name" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> Desc
-> Desc
-> [(Desc, Desc)]
-> Property (HasInfo + DebianLike)
annexWebSite Desc
"/srv/git/joey/tmp.git"
		Desc
"tmp.joeyh.name"
		Desc
"26fd6e38-1226-11e2-a75f-ff007033bdba"
		[]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Times -> Property UnixLike
Cron.jobDropped Desc
"pump rss" (Desc -> Times
Cron.Times Desc
"15 * * * *")

ircBouncer :: Property (HasInfo + DebianLike)
ircBouncer :: Property (HasInfo + DebianLike)
ircBouncer = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"IRC bouncer" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"znc"]
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Property DebianLike
User.accountFor (Desc -> User
User Desc
"znc")
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property UnixLike
File.dirExists (Desc -> Desc
takeDirectory Desc
conf)
	Props DebianLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContent Desc
conf Context
anyContext
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> User -> Group -> Property UnixLike
File.ownerGroup Desc
conf (Desc -> User
User Desc
"znc") (Desc -> Group
Group Desc
"znc")
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Times -> User -> Desc -> Desc -> Property DebianLike
Cron.job Desc
"znconboot" (Desc -> Times
Cron.Times Desc
"@reboot") (Desc -> User
User Desc
"znc") Desc
"~" Desc
"znc"
	-- ensure running if it was not already
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> [Desc] -> UncheckedProperty UnixLike
userScriptProperty (Desc -> User
User Desc
"znc") [Desc
"znc || true"]
		UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
NoChange
		Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"znc running"
  where
	conf :: Desc
conf = Desc
"/home/znc/.znc/configs/znc.conf"

githubBackup :: Property (HasInfo + DebianLike)
githubBackup :: Property (HasInfo + DebianLike)
githubBackup = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"github-backup box" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"github-backup", Desc
"moreutils"]
	Props DebianLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
Property (HasInfo + UnixLike)
githubKeys
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Times -> User -> Desc -> Desc -> Property DebianLike
Cron.niceJob Desc
"github-backup run" (Desc -> Times
Cron.Times Desc
"30 4 * * *") (Desc -> User
User Desc
"joey")
		Desc
"/home/joey/lib/backup" Desc
backupcmd
  where
	backupcmd :: Desc
backupcmd = Desc -> [Desc] -> Desc
forall a. [a] -> [[a]] -> [a]
intercalate Desc
"&&" ([Desc] -> Desc) -> [Desc] -> Desc
forall a b. (a -> b) -> a -> b
$
		[ Desc
"mkdir -p github"
		, Desc
"cd github"
		, Desc
". $HOME/.github-keys"
		, Desc
"github-backup joeyh"
		]

githubKeys :: Property (HasInfo + UnixLike)
githubKeys :: Property (HasInfo + UnixLike)
githubKeys =
	let f :: Desc
f = Desc
"/home/joey/.github-keys"
	in Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContent Desc
f Context
anyContext
		Property
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property UnixLike
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> User -> Group -> Property UnixLike
File.ownerGroup Desc
f (Desc -> User
User Desc
"joey") (Desc -> Group
Group Desc
"joey")


rsyncNetBackup :: [Host] -> Property DebianLike
rsyncNetBackup :: [Host] -> Property DebianLike
rsyncNetBackup [Host]
hosts = Desc -> Times -> User -> Desc -> Desc -> Property DebianLike
Cron.niceJob Desc
"rsync.net copied in daily" (Desc -> Times
Cron.Times Desc
"30 5 * * *")
	(Desc -> User
User Desc
"joey") Desc
"/home/joey/lib/backup" Desc
"mkdir -p rsync.net && rsync --delete -az 2318@usw-s002.rsync.net: rsync.net"
	Property DebianLike
-> Property UnixLike
-> CombinedType (Property DebianLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Host] -> Desc -> User -> Property UnixLike
Ssh.knownHost [Host]
hosts Desc
"usw-s002.rsync.net" (Desc -> User
User Desc
"joey")

podcatcher :: Property DebianLike
podcatcher :: Property DebianLike
podcatcher = Desc -> Times -> User -> Desc -> Desc -> Property DebianLike
Cron.niceJob Desc
"podcatcher run hourly" (Desc -> Times
Cron.Times Desc
"55 * * * *")
	(Desc -> User
User Desc
"joey") Desc
"/home/joey/lib/sound/podcasts"
	Desc
"xargs git-annex importfeed -c annex.genmetadata=true < feeds; mr --quiet update"
	Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Desc] -> Property DebianLike
Apt.installed [Desc
"git-annex", Desc
"myrepos"]

spamdEnabled :: Property DebianLike
spamdEnabled :: Property DebianLike
spamdEnabled = Property UnixLike -> Property DebianLike
forall (p :: * -> *) (untightened :: [MetaType])
       (tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
 SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property UnixLike -> Property DebianLike)
-> Property UnixLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ 
	Desc -> [Desc] -> UncheckedProperty UnixLike
cmdProperty Desc
"update-rc.d" [Desc
"spamassassin", Desc
"enable"]
		UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange

spamassassinConfigured :: Property DebianLike
spamassassinConfigured :: Property DebianLike
spamassassinConfigured = Desc -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"spamassassin configured" (Props DebianLike -> Property DebianLike)
-> Props DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"spamassassin"
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/default/spamassassin" Desc -> [Desc] -> Property UnixLike
`File.containsLines`
		[ Desc
"# Propellor deployed"
		, Desc
"OPTIONS=\"--create-prefs --max-children 5 --helper-home-dir\""
		, Desc
"CRON=1"
		, Desc
"NICE=\"--nicelevel 15\""
		]
		Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"spamd configured"
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
spamdEnabled
		Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"spamassassin"
		Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"cron"

kiteMailServer :: Property (HasInfo + DebianLike)
kiteMailServer :: Property (HasInfo + DebianLike)
kiteMailServer = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"kitenet.net mail server" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
Postfix.installed
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"postfix-pcre"]
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"postgrey"
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
spamassassinConfigured
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"spamass-milter"
	-- Add -m to prevent modifying messages Subject or body.
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/default/spamass-milter" Desc -> Desc -> Property UnixLike
`File.containsLine`
		Desc
"OPTIONS=\"-m -u spamass-milter -i 127.0.0.1\""
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"spamass-milter"
		Property DebianLike -> Desc -> Property DebianLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"spamass-milter configured"

	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"amavisd-milter"
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/default/amavisd-milter" Desc -> [Desc] -> Property UnixLike
`File.containsLines`
		[ Desc
"# Propellor deployed"
		, Desc
"MILTERSOCKET=/var/spool/postfix/amavis/amavis.sock"
		, Desc
"MILTERSOCKETOWNER=\"postfix:postfix\""
		, Desc
"MILTERSOCKETMODE=\"0660\""
		]
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"amavisd-milter"
		Property DebianLike -> Desc -> Property DebianLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"amavisd-milter configured for postfix"
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"clamav-freshclam"
	-- Workaround https://bugs.debian.org/569150
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Times -> User -> Desc -> Desc -> Property DebianLike
Cron.niceJob Desc
"amavis-expire" Times
Cron.Daily (Desc -> User
User Desc
"root") Desc
"/"
		Desc
"find /var/lib/amavis/virusmails/ -type f -ctime +2 -delete"

	Props DebianLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Property (HasInfo + DebianLike)
dkimInstalled

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
Postfix.saslAuthdInstalled
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
Fail2Ban.installed
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Fail2Ban.jailEnabled Desc
"postfix-sasl"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/default/saslauthd" Desc -> Desc -> Property UnixLike
`File.containsLine` Desc
"MECHANISMS=sasldb"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> User -> Property (HasInfo + UnixLike)
Postfix.saslPasswdSet Desc
"kitenet.net" (Desc -> User
User Desc
"errol")
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> User -> Property (HasInfo + UnixLike)
Postfix.saslPasswdSet Desc
"kitenet.net" (Desc -> User
User Desc
"joey")

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"maildrop"]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/maildroprc" Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"# Global maildrop filter file (deployed with propellor)"
		, Desc
"DEFAULT=\"$HOME/Maildir\""
		, Desc
"MAILBOX=\"$DEFAULT/.\""
		, Desc
"# Filter spam to a spam folder, unless .keepspam exists"
		, Desc
"if (/^X-Spam-Status: Yes/)"
		, Desc
"{"
		, Desc
"  `test -e \"$HOME/.keepspam\"`"
		, Desc
"  if ( $RETURNCODE != 0 )"
		, Desc
"  to ${MAILBOX}spam"
		, Desc
"}"
		]
		Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"maildrop configured"

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/aliases" Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
`File.hasPrivContentExposed` Context
ctx
		Property
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property UnixLike
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property UnixLike
Postfix.newaliases
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Context -> Property (HasInfo + UnixLike)
hasPostfixCert Context
ctx

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/postfix/mydomain" Desc -> [Desc] -> Property UnixLike
`File.containsLines`
		[ Desc
"/.*\\.kitenet\\.net/\tOK"
		, Desc
"/ikiwiki\\.info/\tOK"
		, Desc
"/joeyh\\.name/\tOK"
		]
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Postfix.reloaded
		Property DebianLike -> Desc -> Property DebianLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"postfix mydomain file configured"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/postfix/obscure_client_relay.pcre" Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		-- Remove received lines for mails relayed from trusted
		-- clients. These can be a privacy violation, or trigger
		-- spam filters.
		[ Desc
"/^Received: from ([^.]+)\\.kitenet\\.net.*using TLS.*by kitenet\\.net \\(([^)]+)\\) with (E?SMTPS?A?) id ([A-F[:digit:]]+)(.*)/ IGNORE"
		-- Munge local Received line for postfix running on a
		-- trusted client that relays through. These can trigger
		-- spam filters.
		, Desc
"/^Received: by ([^.]+)\\.kitenet\\.net.*/ REPLACE X-Question: 42"
		]
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Postfix.reloaded
		Property DebianLike -> Desc -> Property DebianLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"postfix obscure_client_relay file configured"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> (Desc -> Property UnixLike)
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x.
Combines (Property x) (Property UnixLike) =>
Desc
-> (Desc -> Property x)
-> CombinedType (Property x) (Property UnixLike)
Postfix.mappedFile Desc
"/etc/postfix/virtual"
		((Desc -> [Desc] -> Property UnixLike)
-> [Desc] -> Desc -> Property UnixLike
forall a b c. (a -> b -> c) -> b -> a -> c
flip Desc -> [Desc] -> Property UnixLike
File.containsLines
			[ Desc
"# *@joeyh.name to joey"
			, Desc
"@joeyh.name\tjoey"
			]
		) Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"postfix virtual file configured"
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Postfix.reloaded
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> (Desc
    -> Property
         (Sing
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
               'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property UnixLike)
forall x.
Combines (Property x) (Property UnixLike) =>
Desc
-> (Desc -> Property x)
-> CombinedType (Property x) (Property UnixLike)
Postfix.mappedFile Desc
"/etc/postfix/relay_clientcerts"
		((Desc
 -> Context
 -> Property
      (Sing
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Context
-> Desc
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b c. (a -> b -> c) -> b -> a -> c
flip Desc
-> Context
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContentExposed Context
ctx)
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
Postfix.mainCfFile Desc -> [Desc] -> Property UnixLike
`File.containsLines`
		[ Desc
"myhostname = kitenet.net"
		, Desc
"mydomain = $myhostname"
		, Desc
"append_dot_mydomain = no"
		, Desc
"myorigin = kitenet.net"
		, Desc
"mydestination = $myhostname, localhost.$mydomain, $mydomain, kite.$mydomain., localhost, regexp:$config_directory/mydomain"
		, Desc
"mailbox_command = maildrop"
		, Desc
"virtual_alias_maps = hash:/etc/postfix/virtual"

		, Desc
"# Allow clients with trusted certs to relay mail through."
		, Desc
"relay_clientcerts = hash:/etc/postfix/relay_clientcerts"
		, Desc
"smtpd_relay_restrictions = permit_mynetworks,permit_tls_clientcerts,permit_sasl_authenticated,reject_unauth_destination"

		, Desc
"# Filter out client relay lines from headers."
		, Desc
"header_checks = pcre:$config_directory/obscure_client_relay.pcre"

		, Desc
"# Password auth for relaying"
		, Desc
"smtpd_sasl_auth_enable = yes"
		, Desc
"smtpd_sasl_security_options = noanonymous"
		, Desc
"smtpd_sasl_local_domain = kitenet.net"

		, Desc
"# Enable postgrey and sasl auth and client certs."
		, Desc
"smtpd_recipient_restrictions = permit_tls_clientcerts,permit_sasl_authenticated,,permit_mynetworks,reject_unauth_destination,check_policy_service inet:127.0.0.1:10023"

		, Desc
"# Enable spamass-milter, amavis-milter (opendkim is not enabled because it causes mails forwarded from eg gmail to be rejected)"
		, Desc
"smtpd_milters = unix:/spamass/spamass.sock unix:amavis/amavis.sock"
		, Desc
"# opendkim is used for outgoing mail"
		, Desc
"non_smtpd_milters = inet:localhost:8891"
		, Desc
"milter_connect_macros = j {daemon_name} v {if_name} _"
		, Desc
"# If a milter is broken, fall back to just accepting mail."
		, Desc
"milter_default_action = accept"

		, Desc
"# TLS setup -- server"
		, Desc
"smtpd_tls_CAfile = /etc/ssl/certs/joeyca.pem"
		, Desc
"smtpd_tls_cert_file = /etc/ssl/certs/postfix.pem"
		, Desc
"smtpd_tls_key_file = /etc/ssl/private/postfix.pem"
		, Desc
"smtpd_tls_loglevel = 1"
		, Desc
"smtpd_tls_received_header = yes"
		, Desc
"smtpd_use_tls = yes"
		, Desc
"smtpd_tls_ask_ccert = yes"
		, Desc
"smtpd_tls_session_cache_database = sdbm:/etc/postfix/smtpd_scache"

		, Desc
"# TLS setup -- client"
		, Desc
"smtp_tls_CAfile = /etc/ssl/certs/joeyca.pem"
		, Desc
"smtp_tls_cert_file = /etc/ssl/certs/postfix.pem"
		, Desc
"smtp_tls_key_file = /etc/ssl/private/postfix.pem"
		, Desc
"smtp_tls_loglevel = 1"
		, Desc
"smtp_use_tls = yes"
		, Desc
"smtp_tls_session_cache_database = sdbm:/etc/postfix/smtp_scache"

		, Desc
"# Allow larger attachments, up to 200 mb."
		, Desc
"# (Avoid setting too high; the postfix queue must have"
		, Desc
"# 1.5 times this much space free, or postfix will reject"
		, Desc
"# ALL mail!)"
		, Desc
"message_size_limit = 204800000"
		, Desc
"virtual_mailbox_limit = 20480000"
		]
		Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property UnixLike
Postfix.dedupMainCf
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Postfix.reloaded
		Property DebianLike -> Desc -> Property DebianLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"postfix configured"

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"dovecot-imapd"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"dovecot-pop3d"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/dovecot/conf.d/10-mail.conf" Desc -> Desc -> Property UnixLike
`File.containsLine`
		Desc
"mail_location = maildir:~/Maildir"
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.reloaded Desc
"dovecot"
		Property DebianLike -> Desc -> Property DebianLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"dovecot mail.conf"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/dovecot/conf.d/10-auth.conf" Desc -> Desc -> Property UnixLike
`File.containsLine`
		Desc
"!include auth-passwdfile.conf.ext"
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"dovecot"
		Property DebianLike -> Desc -> Property DebianLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"dovecot auth.conf"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContent Desc
dovecotusers Context
ctx
		Property
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property UnixLike
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` (Desc
dovecotusers Desc -> FileMode -> Property UnixLike
`File.mode`
			[FileMode] -> FileMode
combineModes [FileMode
ownerReadMode, FileMode
groupReadMode])
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> User -> Group -> Property UnixLike
File.ownerGroup Desc
dovecotusers (Desc -> User
User Desc
"root") (Desc -> Group
Group Desc
"dovecot")

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"mutt", Desc
"bsd-mailx", Desc
"alpine"]

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
pinescript Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"#!/bin/sh"
		, Desc
"# deployed with propellor"
		, Desc
"set -e"
		, Desc
"exec alpine \"$@\""
		]
		Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` (Desc
pinescript Desc -> FileMode -> Property UnixLike
`File.mode`
			[FileMode] -> FileMode
combineModes ([FileMode]
readModes [FileMode] -> [FileMode] -> [FileMode]
forall a. [a] -> [a] -> [a]
++ [FileMode]
executeModes))
		Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"pine wrapper script"
	-- Make pine use dovecot pipe to read maildir.
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/pine.conf" Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"# deployed with propellor"
		, Desc
"inbox-path={localhost}inbox"
		, Desc
"rsh-command=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
imapalpinescript
		]
		Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"pine configured to use local imap server"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
imapalpinescript Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"#!/bin/sh"
		, Desc
"# deployed with propellor"
		, Desc
"set -e"
		, Desc
"exec /usr/lib/dovecot/imap 2>/dev/null"
		]
		Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` (Desc
imapalpinescript Desc -> FileMode -> Property UnixLike
`File.mode`
			[FileMode] -> FileMode
combineModes ([FileMode]
readModes [FileMode] -> [FileMode] -> [FileMode]
forall a. [a] -> [a] -> [a]
++ [FileMode]
executeModes))
		Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"imap script for pine"
	-- XXX temporarily disabled installing as it's not available in
	-- debian unstable any longer. Need to upgrade to mailman3
	-- at some point. (nontrivial)
	-- & Apt.serviceInstalledRunning "mailman"
	-- Override the default http url. (Only affects new lists.)
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/mailman/mm_cfg.py" Desc -> Desc -> Property UnixLike
`File.containsLine`
		Desc
"DEFAULT_URL_PATTERN = 'https://%s/cgi-bin/mailman/'"

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Service -> RevertableProperty DebianLike DebianLike
Postfix.service Service
ssmtp

	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"fetchmail"]
  where
	ctx :: Context
ctx = Desc -> Context
Context Desc
"kitenet.net"
	pinescript :: Desc
pinescript = Desc
"/usr/local/bin/pine"
	imapalpinescript :: Desc
imapalpinescript = Desc
"/usr/local/bin/imap-for-alpine"
	dovecotusers :: Desc
dovecotusers = Desc
"/etc/dovecot/users"

	ssmtp :: Service
ssmtp = ServiceType -> Desc -> ServiceOpts -> Service
Postfix.Service
		(Maybe Desc -> Desc -> ServiceType
Postfix.InetService Maybe Desc
forall a. Maybe a
Nothing Desc
"ssmtp")
		Desc
"smtpd" ServiceOpts
Postfix.defServiceOpts

-- Configures postfix to have the dkim milter, and no other milters.
dkimMilter :: Property (HasInfo + DebianLike)
dkimMilter :: Property (HasInfo + DebianLike)
dkimMilter = Desc
Postfix.mainCfFile Desc -> [Desc] -> Property UnixLike
`File.containsLines`
	[ Desc
"smtpd_milters = inet:localhost:8891"
	, Desc
"non_smtpd_milters = inet:localhost:8891"
	, Desc
"milter_default_action = accept"
	]
	Property UnixLike -> Desc -> Property UnixLike
forall p. IsProp p => p -> Desc -> p
`describe` Desc
"postfix dkim milter"
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property UnixLike
Postfix.dedupMainCf
	Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Postfix.reloaded
	Property DebianLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> CombinedType
     (Property DebianLike)
     (Property
        (MetaTypes
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Property (HasInfo + DebianLike)
dkimInstalled
	Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> CombinedType
     (Property
        (MetaTypes
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
     (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
Postfix.installed

-- This does not configure postfix to use the dkim milter,
-- nor does it set up domainkey DNS.
dkimInstalled :: Property (HasInfo + DebianLike)
dkimInstalled :: Property (HasInfo + DebianLike)
dkimInstalled = Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
go Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> CombinedType
     (Property
        (MetaTypes
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
     (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"opendkim"
  where
	go :: Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
go = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"opendkim installed" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"opendkim"
		Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property UnixLike
File.dirExists Desc
"/etc/mail"
		Props DebianLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContent Desc
"/etc/mail/dkim.key" (Desc -> Context
Context Desc
"kitenet.net")
		Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> User -> Group -> Property UnixLike
File.ownerGroup Desc
"/etc/mail/dkim.key" (Desc -> User
User Desc
"root") (Desc -> Group
Group Desc
"root")
		Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/default/opendkim" Desc -> Desc -> Property UnixLike
`File.containsLine`
			Desc
"SOCKET=\"inet:8891@localhost\""
			Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` 
				(Desc -> [Desc] -> UncheckedProperty UnixLike
cmdProperty Desc
"/lib/opendkim/opendkim.service.generate" []
				UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange)
			Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"opendkim"
		Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/opendkim.conf" Desc -> [Desc] -> Property UnixLike
`File.containsLines`
			[ Desc
"KeyFile /etc/mail/dkim.key"
			, Desc
"SubDomains yes"
			, Desc
"Domain *"
			, Desc
"Selector mail"
			]

-- This is the dkim public key, corresponding with /etc/mail/dkim.key
-- This value can be included in a domain's additional records to make
-- it use this domainkey.
domainKey :: (BindDomain, Record)
domainKey :: (BindDomain, Record)
domainKey = (Desc -> BindDomain
RelDomain Desc
"mail._domainkey", Desc -> Record
TXT Desc
"v=DKIM1; k=rsa; p=MIGfMA0GCSqGSIb3DQEBAQUAA4GNADCBiQKBgQCc+/rfzNdt5DseBBmfB3C6sVM7FgVvf4h1FeCfyfwPpVcmPdW6M2I+NtJsbRkNbEICxiP6QY2UM0uoo9TmPqLgiCCG2vtuiG6XMsS0Y/gGwqKM7ntg/7vT1Go9vcquOFFuLa5PnzpVf8hB9+PMFdS4NPTvWL2c5xxshl/RJzICnQIDAQAB")

postfixSaslPasswordClient :: Property (HasInfo + DebianLike)
postfixSaslPasswordClient :: Property (HasInfo + DebianLike)
postfixSaslPasswordClient = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties Desc
"postfix uses SASL password to authenticate with smarthost" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> (Desc
    -> Property
         (Sing
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
               'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> CombinedType
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property UnixLike)
forall x.
Combines (Property x) (Property UnixLike) =>
Desc
-> (Desc -> Property x)
-> CombinedType (Property x) (Property UnixLike)
Postfix.mappedFile Desc
"/etc/postfix/sasl_passwd" 
		(Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
`File.hasPrivContent` (Desc -> Context
Context Desc
"kitenet.net"))
	Props
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
Postfix.mainCfFile Desc -> [Desc] -> Property UnixLike
`File.containsLines`
		[ Desc
"# TLS setup for SASL auth to kite"
		, Desc
"smtp_sasl_auth_enable = yes"
		, Desc
"smtp_tls_security_level = encrypt"
		, Desc
"smtp_sasl_tls_security_options = noanonymous"
		, Desc
"relayhost = [kitenet.net]"
		, Desc
"smtp_sasl_password_maps = hash:/etc/postfix/sasl_passwd"
		]
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Postfix.reloaded
	-- Comes after so it does not set relayhost but uses the setting 
	-- above.
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
Postfix.satellite

hasPostfixCert :: Context -> Property (HasInfo + UnixLike)
hasPostfixCert :: Context -> Property (HasInfo + UnixLike)
hasPostfixCert Context
ctx = Desc
-> Props
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties Desc
"postfix tls cert installed" (Props
   (Sing
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
 -> Property
      (Sing
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Props
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/ssl/certs/postfix.pem" Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
`File.hasPrivContentExposed` Context
ctx
	Props
  (Sing
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/ssl/private/postfix.pem" Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
`File.hasPrivContent` Context
ctx

-- Legacy static web sites and redirections from kitenet.net to newer
-- sites.
legacyWebSites :: Property (HasInfo + DebianLike)
legacyWebSites :: Property (HasInfo + DebianLike)
legacyWebSites = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"legacy web sites" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"apache2"
	Props DebianLike
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> RevertableProperty DebianLike DebianLike
Apache.modEnabled Desc
"rewrite"
	Props DebianLike
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> RevertableProperty DebianLike DebianLike
Apache.modEnabled Desc
"cgi"
	Props DebianLike
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> RevertableProperty DebianLike DebianLike
Apache.modEnabled Desc
"speling"
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
userDirHtml
	Props DebianLike
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> Desc
-> AgreeTOS
-> [Desc]
-> RevertableProperty DebianLike DebianLike
Apache.httpsVirtualHost' Desc
"kitenet.net" Desc
"/var/www" AgreeTOS
letos [Desc]
kitenetcfg
	Props DebianLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
"anna.kitenet.net"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> RevertableProperty DebianLike DebianLike
apacheSite Desc
"anna.kitenet.net"
		[ Desc
"DocumentRoot /home/anna/html"
		, Desc
"<Directory /home/anna/html/>"
		, Desc
"  Options Indexes ExecCGI"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"
		]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
"sows-ear.kitenet.net"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
"www.sows-ear.kitenet.net"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> RevertableProperty DebianLike DebianLike
apacheSite Desc
"sows-ear.kitenet.net"
		[ Desc
"ServerAlias www.sows-ear.kitenet.net"
		, Desc
"DocumentRoot /srv/web/sows-ear.kitenet.net"
		, Desc
"<Directory /srv/web/sows-ear.kitenet.net>"
		, Desc
"  Options FollowSymLinks"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"
		, Desc
"RewriteEngine On"
		, Desc
"RewriteRule .* http://www.sowsearpoetry.org/ [L]"
		]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
"wortroot.kitenet.net"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
"www.wortroot.kitenet.net"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> RevertableProperty DebianLike DebianLike
apacheSite Desc
"wortroot.kitenet.net"
		[ Desc
"ServerAlias www.wortroot.kitenet.net"
		, Desc
"DocumentRoot /srv/web/wortroot.kitenet.net"
		, Desc
"<Directory /srv/web/wortroot.kitenet.net>"
		, Desc
"  Options FollowSymLinks"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"
		]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
"creeksidepress.com"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> RevertableProperty DebianLike DebianLike
apacheSite Desc
"creeksidepress.com"
		[ Desc
"ServerAlias www.creeksidepress.com"
		, Desc
"DocumentRoot /srv/web/www.creeksidepress.com"
		, Desc
"<Directory /srv/web/www.creeksidepress.com>"
		, Desc
"  Options FollowSymLinks"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"
		]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
"joey.kitenet.net"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> RevertableProperty DebianLike DebianLike
apacheSite Desc
"joey.kitenet.net"
		[ Desc
"DocumentRoot /var/www"
		, Desc
"<Directory /var/www/>"
		, Desc
"  Options Indexes ExecCGI"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"

		, Desc
"RewriteEngine On"

		, Desc
"# Old ikiwiki filenames for joey's wiki."
		, Desc
"rewritecond $1 !.*/index$"
		, Desc
"rewriterule (.+).html$ http://joeyh.name/$1/ [l]"

		, Desc
"rewritecond $1 !.*/index$"
		, Desc
"rewriterule (.+).rss$ http://joeyh.name/$1/index.rss [l]"

		, Desc
"# Redirect all to joeyh.name."
		, Desc
"rewriterule (.*) http://joeyh.name$1 [r]"
		]
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property (HasInfo + UnixLike)
alias Desc
"house.joeyh.name"
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> RevertableProperty DebianLike DebianLike
apacheSite Desc
"house.joeyh.name"
		[ Desc
"DocumentRoot /srv/web/house.joeyh.name"
		, Desc
"<Directory /srv/web/house.joeyh.name>"
		, Desc
"  Options Indexes ExecCGI"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"
		]
  where
	kitenetcfg :: [Desc]
kitenetcfg =
		-- /var/www is empty
		[ Desc
"DocumentRoot /var/www"
		, Desc
"<Directory /var/www>"
		, Desc
"  Options Indexes FollowSymLinks MultiViews ExecCGI Includes"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"
		, Desc
"ScriptAlias /cgi-bin/ /usr/lib/cgi-bin/"

		-- for mailman cgi scripts
		, Desc
"<Directory /usr/lib/cgi-bin>"
		, Desc
"  AllowOverride None"
		, Desc
"  Options ExecCGI"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"
		, Desc
"Alias /pipermail/ /var/lib/mailman/archives/public/"
		, Desc
"<Directory /var/lib/mailman/archives/public/>"
		, Desc
"  Options Indexes MultiViews FollowSymlinks"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"
		, Desc
"Alias /images/ /usr/share/images/"
		, Desc
"<Directory /usr/share/images/>"
		, Desc
"  Options Indexes MultiViews"
		, Desc
"  AllowOverride None"
		, Desc
Apache.allowAll
		, Desc
"</Directory>"

		, Desc
"RewriteEngine On"
		, Desc
"# Force hostname to kitenet.net"
		, Desc
"RewriteCond %{HTTP_HOST} !^kitenet\\.net [NC]"
		, Desc
"RewriteCond %{HTTP_HOST} !^$"
		, Desc
"RewriteRule ^/(.*) http://kitenet\\.net/$1 [L,R]"

		, Desc
"# Moved pages"
		, Desc
"RewriteRule /programs/debhelper http://joeyh.name/code/debhelper/ [L]"
		, Desc
"RewriteRule /programs/satutils http://joeyh.name/code/satutils/ [L]"
		, Desc
"RewriteRule /programs/filters http://joeyh.name/code/filters/ [L]"
		, Desc
"RewriteRule /programs/ticker http://joeyh.name/code/ticker/ [L]"
		, Desc
"RewriteRule /programs/pdmenu http://joeyh.name/code/pdmenu/ [L]"
		, Desc
"RewriteRule /programs/sleepd http://joeyh.name/code/sleepd/ [L]"
		, Desc
"RewriteRule /programs/Lingua::EN::Words2Nums http://joeyh.name/code/Words2Nums/ [L]"
		, Desc
"RewriteRule /programs/wmbattery http://joeyh.name/code/wmbattery/ [L]"
		, Desc
"RewriteRule /programs/dpkg-repack http://joeyh.name/code/dpkg-repack/ [L]"
		, Desc
"RewriteRule /programs/debconf http://joeyh.name/code/debconf/ [L]"
		, Desc
"RewriteRule /programs/perlmoo http://joeyh.name/code/perlmoo/ [L]"
		, Desc
"RewriteRule /programs/alien http://joeyh.name/code/alien/ [L]"
		, Desc
"RewriteRule /~joey/blog/entry/(.+)-[0-9][0-9][0-9][0-9]-[0-9][0-9]-[0-9][0-9]-[0-9][0-9]-[0-9][0-9].html http://joeyh.name/blog/entry/$1/ [L]"
		, Desc
"RewriteRule /~anna/.* http://waldeneffect\\.org/ [R]"
		, Desc
"RewriteRule /~anna/.* http://waldeneffect\\.org/ [R]"
		, Desc
"RewriteRule /~anna http://waldeneffect\\.org/ [R]"
		, Desc
"RewriteRule /simpleid/ http://openid.kitenet.net:8086/simpleid/"
		, Desc
"# Even the kite home page is not here any more!"
		, Desc
"RewriteRule ^/$ http://www.kitenet.net/ [R]"
		, Desc
"RewriteRule ^/index.html http://www.kitenet.net/ [R]"
		, Desc
"RewriteRule ^/joey http://www.kitenet.net/joey/ [R]"
		, Desc
"RewriteRule ^/joey/index.html http://www.kitenet.net/joey/ [R]"
		, Desc
"RewriteRule ^/wifi http://www.kitenet.net/wifi/ [R]"
		, Desc
"RewriteRule ^/wifi/index.html http://www.kitenet.net/wifi/ [R]"

		, Desc
"# Old ikiwiki filenames for kitenet.net wiki."
		, Desc
"rewritecond $1 !^/~"
		, Desc
"rewritecond $1 !^/doc/"
		, Desc
"rewritecond $1 !^/pipermail/"
		, Desc
"rewritecond $1 !^/cgi-bin/"
		, Desc
"rewritecond $1 !.*/index$"
		, Desc
"rewriterule (.+).html$ $1/ [r]"

		, Desc
"# Old ikiwiki filenames for joey's wiki."
		, Desc
"rewritecond $1 ^/~joey/"
		, Desc
"rewritecond $1 !.*/index$"
		, Desc
"rewriterule (.+).html$ http://kitenet.net/$1/ [L,R]"

		, Desc
"# ~joey to joeyh.name"
		, Desc
"rewriterule /~joey/(.*) http://joeyh.name/$1 [L]"

		, Desc
"# Old familywiki location."
		, Desc
"rewriterule /~family/(.*).html http://family.kitenet.net/$1 [L]"
		, Desc
"rewriterule /~family/(.*).rss http://family.kitenet.net/$1/index.rss [L]"
		, Desc
"rewriterule /~family(.*) http://family.kitenet.net$1 [L]"

		, Desc
"rewriterule /~kyle/bywayofscience(.*) http://bywayofscience.branchable.com$1 [L]"
		, Desc
"rewriterule /~kyle/family/wiki/(.*).html http://macleawiki.branchable.com/$1 [L]"
		, Desc
"rewriterule /~kyle/family/wiki/(.*).rss http://macleawiki.branchable.com/$1/index.rss [L]"
		, Desc
"rewriterule /~kyle/family/wiki(.*) http://macleawiki.branchable.com$1 [L]"
		]

userDirHtml :: Property DebianLike
userDirHtml :: Property DebianLike
userDirHtml = Desc -> ([Desc] -> [Desc]) -> Desc -> Property UnixLike
forall c.
(FileContent c, Eq c) =>
Desc -> (c -> c) -> Desc -> Property UnixLike
File.fileProperty Desc
"apache userdir is html" ((Desc -> Desc) -> [Desc] -> [Desc]
forall a b. (a -> b) -> [a] -> [b]
map Desc -> Desc
munge) Desc
conf
	Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Apache.reloaded
	Property DebianLike
-> RevertableProperty DebianLike DebianLike
-> CombinedType
     (Property DebianLike) (RevertableProperty DebianLike DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> RevertableProperty DebianLike DebianLike
Apache.modEnabled Desc
"userdir"
  where
	munge :: Desc -> Desc
munge = Desc -> Desc -> Desc -> Desc
forall a. Eq a => [a] -> [a] -> [a] -> [a]
replace Desc
"public_html" Desc
"html"
	conf :: Desc
conf = Desc
"/etc/apache2/mods-available/userdir.conf"

-- Alarm clock: see
-- <http://joeyh.name/blog/entry/a_programmable_alarm_clock_using_systemd/>
--
-- oncalendar example value: "*-*-* 7:30"
alarmClock :: String -> User -> String -> Property Linux
alarmClock :: Desc -> User -> Desc -> Property Linux
alarmClock Desc
oncalendar (User Desc
user) Desc
command = Desc -> Props Linux -> Property Linux
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties Desc
"goodmorning timer installed" (Props Linux -> Property Linux) -> Props Linux -> Property Linux
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/systemd/system/goodmorning.timer" Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"[Unit]"
		, Desc
"Description=good morning"
		, Desc
""
		, Desc
"[Timer]"
		, Desc
"Unit=goodmorning.service"
		, Desc
"OnCalendar=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
oncalendar
		, Desc
"WakeSystem=true"
		, Desc
"Persistent=false"
		, Desc
""
		, Desc
"[Install]"
		, Desc
"WantedBy=multi-user.target"
		]
		Property UnixLike
-> Property Linux
-> CombinedType (Property UnixLike) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` (Property Linux
Systemd.daemonReloaded
			Property Linux
-> Property Linux -> CombinedType (Property Linux) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Desc -> Property Linux
Systemd.restarted Desc
"goodmorning.timer")
	Props Linux
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/systemd/system/goodmorning.service" Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"[Unit]"
		, Desc
"Description=good morning"
		, Desc
"RefuseManualStart=true"
		, Desc
"RefuseManualStop=true"
		, Desc
"ConditionACPower=true"
		, Desc
"StopWhenUnneeded=yes"
		, Desc
""
		, Desc
"[Service]"
		, Desc
"Type=oneshot"
		, Desc
"ExecStart=/bin/systemd-inhibit --what=handle-lid-switch --why=goodmorning /bin/su " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
user Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
" -c \"" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
command Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"\""
		]
		Property UnixLike
-> Property Linux
-> CombinedType (Property UnixLike) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property Linux
Systemd.daemonReloaded
	Props Linux
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.enabled Desc
"goodmorning.timer"
	Props Linux
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.started Desc
"goodmorning.timer"
	Props Linux
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/systemd/logind.conf" Desc -> (Desc, Desc, Desc) -> Property UnixLike
`ConfFile.containsIniSetting`
		(Desc
"Login", Desc
"LidSwitchIgnoreInhibited", Desc
"no")

house :: IsContext c => User -> [Host] -> c -> (SshKeyType, Ssh.PubKeyText) -> Property (HasInfo + DebianLike)
house :: User
-> [Host]
-> c
-> (SshKeyType, Desc)
-> Property (HasInfo + DebianLike)
house User
user [Host]
hosts c
ctx (SshKeyType, Desc)
sshkey = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"home automation" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
Apache.installed
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"libmodbus-dev", Desc
"rrdtool", Desc
"rsync"]
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Desc -> Desc -> Maybe Desc -> Property DebianLike
Git.cloned User
user Desc
"https://git.joeyh.name/git/joey/house.git" Desc
d Maybe Desc
forall a. Maybe a
Nothing
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Desc -> Desc -> Maybe Desc -> Property DebianLike
Git.cloned User
user Desc
"https://git.joeyh.name/git/reactive-banana-automation.git" (Desc
d Desc -> Desc -> Desc
</> Desc
"reactive-banana-automation") Maybe Desc
forall a. Maybe a
Nothing
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Desc -> Desc -> Maybe Desc -> Property DebianLike
Git.cloned User
user Desc
"https://git.joeyh.name/git/haskell-libmodbus.git" (Desc
d Desc -> Desc -> Desc
</> Desc
"haskell-libmodbus") Maybe Desc
forall a. Maybe a
Nothing
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property UnixLike
websitesymlink
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
build
	Props DebianLike
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.enabled Desc
setupservicename
		Property Linux
-> Property UnixLike
-> CombinedType (Property Linux) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property UnixLike
setupserviceinstalled
		Property Linux
-> Property Linux -> CombinedType (Property Linux) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property Linux
Systemd.started Desc
setupservicename
	Props DebianLike
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.enabled Desc
pollerservicename
		Property Linux
-> Property UnixLike
-> CombinedType (Property Linux) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property UnixLike
pollerserviceinstalled
		Property Linux
-> Property Linux -> CombinedType (Property Linux) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property Linux
Systemd.started Desc
pollerservicename
	Props DebianLike
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.enabled Desc
controllerservicename
		Property Linux
-> Property UnixLike
-> CombinedType (Property Linux) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property UnixLike
controllerserviceinstalled
		Property Linux
-> Property Linux -> CombinedType (Property Linux) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property Linux
Systemd.started Desc
controllerservicename
	Props DebianLike
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.enabled Desc
watchdogservicename
		Property Linux
-> Property UnixLike
-> CombinedType (Property Linux) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property UnixLike
watchdogserviceinstalled
		Property Linux
-> Property Linux -> CombinedType (Property Linux) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property Linux
Systemd.started Desc
watchdogservicename
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
Apt.serviceInstalledRunning Desc
"watchdog"
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Group -> Property DebianLike
User.hasGroup User
user (Desc -> Group
Group Desc
"dialout")
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Group -> Maybe Int -> Property UnixLike
Group.exists (Desc -> Group
Group Desc
"gpio") Maybe Int
forall a. Maybe a
Nothing
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Group -> Property DebianLike
User.hasGroup User
user (Desc -> Group
Group Desc
"gpio")
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"i2c-tools"]
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& User -> Group -> Property DebianLike
User.hasGroup User
user (Desc -> Group
Group Desc
"i2c")
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/modules-load.d/house.conf" Desc -> [Desc] -> Property UnixLike
`File.hasContent` [Desc
"i2c-dev"]
	Props DebianLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Times -> User -> Desc -> Desc -> Property DebianLike
Cron.niceJob Desc
"house upload"
		(Desc -> Times
Cron.Times Desc
"1 * * * *") User
user Desc
d Desc
rsynccommand
		Property DebianLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> CombinedType
     (Property DebianLike)
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Maybe Desc
-> User -> c -> (SshKeyType, Desc) -> Property (HasInfo + UnixLike)
forall c.
IsContext c =>
Maybe Desc
-> User -> c -> (SshKeyType, Desc) -> Property (HasInfo + UnixLike)
Ssh.userKeyAt (Desc -> Maybe Desc
forall a. a -> Maybe a
Just Desc
sshkeyfile) User
user c
ctx (SshKeyType, Desc)
sshkey
		Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> CombinedType
     (Property
        (MetaTypes
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
     (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> User -> Group -> Property UnixLike
File.ownerGroup (Desc -> Desc
takeDirectory Desc
sshkeyfile)
			User
user (User -> Group
userGroup User
user)
		Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> CombinedType
     (Property
        (MetaTypes
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
     (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> Property UnixLike
File.dirExists (Desc -> Desc
takeDirectory Desc
sshkeyfile)
		Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property UnixLike
-> CombinedType
     (Property
        (MetaTypes
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
     (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Host] -> Desc -> User -> Property UnixLike
Ssh.knownHost [Host]
hosts Desc
"kitenet.net" User
user
	Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContentExposed Desc
"/etc/darksky-forecast-url" Context
anyContext
  where
	d :: Desc
d = Desc
"/home/joey/house"
	sshkeyfile :: Desc
sshkeyfile = Desc
d Desc -> Desc -> Desc
</> Desc
".ssh/key"
	build :: Property DebianLike
build = IO Bool -> Property DebianLike -> Property DebianLike
forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Bool -> Bool
not (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Desc -> IO Bool
doesFileExist (Desc
d Desc -> Desc -> Desc
</> Desc
"controller")) (Property DebianLike -> Property DebianLike)
-> Property DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$
		User -> [Desc] -> UncheckedProperty UnixLike
userScriptProperty (Desc -> User
User Desc
"joey")
			[ Desc
"cd " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d Desc -> Desc -> Desc
</> Desc
"reactive-banana-automation"
			, Desc
"cabal install"
			, Desc
"cd " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d Desc -> Desc -> Desc
</> Desc
"haskell-libmodbus"
			, Desc
"cabal install"
			, Desc
"cd " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d
			, Desc
"make"
			]
		UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Desc] -> Property DebianLike
Apt.installed
			[ Desc
"ghc", Desc
"cabal-install", Desc
"make"
			, Desc
"libghc-http-types-dev"
			, Desc
"libghc-aeson-dev"
			, Desc
"libghc-wai-dev"
			, Desc
"libghc-warp-dev"
			, Desc
"libghc-http-client-dev"
			, Desc
"libghc-http-client-tls-dev"
			, Desc
"libghc-reactive-banana-dev"
			, Desc
"libghc-hinotify-dev"
			]
	pollerservicename :: Desc
pollerservicename = Desc
"house-poller"
	pollerservicefile :: Desc
pollerservicefile = Desc
"/etc/systemd/system/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
pollerservicename Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
".service"
	pollerserviceinstalled :: Property UnixLike
pollerserviceinstalled = Desc
pollerservicefile Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"[Unit]"
		, Desc
"Description=house poller"
		, Desc
""
		, Desc
"[Service]"
		, Desc
"ExecStart=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"/poller"
		, Desc
"WorkingDirectory=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d
		, Desc
"User=joey"
		, Desc
"Group=joey"
		, Desc
"Restart=always"
		, Desc
""
		, Desc
"[Install]"
		, Desc
"WantedBy=multi-user.target"
		, Desc
"WantedBy=house-controller.target"
		]
	controllerservicename :: Desc
controllerservicename = Desc
"house-controller"
	controllerservicefile :: Desc
controllerservicefile = Desc
"/etc/systemd/system/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
controllerservicename Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
".service"
	controllerserviceinstalled :: Property UnixLike
controllerserviceinstalled = Desc
controllerservicefile Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"[Unit]"
		, Desc
"Description=house controller"
		, Desc
""
		, Desc
"[Service]"
		, Desc
"ExecStart=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"/controller"
		, Desc
"WorkingDirectory=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d
		, Desc
"User=joey"
		, Desc
"Group=joey"
		, Desc
"Restart=always"
		, Desc
""
		, Desc
"[Install]"
		, Desc
"WantedBy=multi-user.target"
		]
	watchdogservicename :: Desc
watchdogservicename = Desc
"house-watchdog"
	watchdogservicefile :: Desc
watchdogservicefile = Desc
"/etc/systemd/system/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
watchdogservicename Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
".service"
	watchdogserviceinstalled :: Property UnixLike
watchdogserviceinstalled = Desc
watchdogservicefile Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"[Unit]"
		, Desc
"Description=house watchdog"
		, Desc
""
		, Desc
"[Service]"
		, Desc
"ExecStart=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"/watchdog"
		, Desc
"WorkingDirectory=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d
		, Desc
"User=root"
		, Desc
"Group=root"
		, Desc
"Restart=always"
		, Desc
""
		, Desc
"[Install]"
		, Desc
"WantedBy=multi-user.target"
		]
	setupservicename :: Desc
setupservicename = Desc
"house-setup"
	setupservicefile :: Desc
setupservicefile = Desc
"/etc/systemd/system/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
setupservicename Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
".service"
	setupserviceinstalled :: Property UnixLike
setupserviceinstalled = Desc
setupservicefile Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"[Unit]"
		, Desc
"Description=house setup"
		, Desc
""
		, Desc
"[Service]"
		, Desc
"ExecStart=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"/setup"
		, Desc
"WorkingDirectory=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d
		, Desc
"User=root"
		, Desc
"Group=root"
		, Desc
"Type=oneshot"
		, Desc
""
		, Desc
"[Install]"
		, Desc
"WantedBy=multi-user.target"
		, Desc
"WantedBy=house-poller.target"
		, Desc
"WantedBy=house-controller.target"
		, Desc
"WantedBy=house-watchdog.target"
		]
	-- Any changes to the rsync command will need my .authorized_keys
	-- rsync server command to be updated too.
	rsynccommand :: Desc
rsynccommand = Desc
"rsync -e 'ssh -i" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
sshkeyfile Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"' -avz rrds/ joey@kitenet.net:/srv/web/house.joeyh.name/rrds/ >/dev/null 2>&1"

	websitesymlink :: Property UnixLike
	websitesymlink :: Property UnixLike
websitesymlink = IO Bool -> Property UnixLike -> Property UnixLike
forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Bool -> Bool
not (Bool -> Bool) -> (FileStatus -> Bool) -> FileStatus -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileStatus -> Bool
isSymbolicLink (FileStatus -> Bool) -> IO FileStatus -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Desc -> IO FileStatus
getSymbolicLinkStatus Desc
"/var/www/html")
		(Desc -> Propellor Result -> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
Desc -> Propellor Result -> Property (MetaTypes metatypes)
property Desc
"website symlink" (Propellor Result -> Property UnixLike)
-> Propellor Result -> Property UnixLike
forall a b. (a -> b) -> a -> b
$ IO () -> Propellor Result
makeChange (IO () -> Propellor Result) -> IO () -> Propellor Result
forall a b. (a -> b) -> a -> b
$ do
			Desc -> IO ()
removeDirectoryRecursive Desc
"/var/www/html"
			Desc -> Desc -> IO ()
createSymbolicLink Desc
d Desc
"/var/www/html"
		)

homerouterWifiInterface :: String
homerouterWifiInterface :: Desc
homerouterWifiInterface = Desc
"wlx9cefd5fcd6f3"

homerouterWifiInterfaceOld :: String
homerouterWifiInterfaceOld :: Desc
homerouterWifiInterfaceOld = Desc
"wlx7cdd90753b9f"

-- My home router, running hostapd and dnsmasq,
-- with eth0 connected to a satellite modem, and a fallback ppp connection.
homeRouter :: Property (HasInfo + DebianLike)
homeRouter :: Property (HasInfo + DebianLike)
homeRouter = Desc
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"home router" (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property UnixLike
File.notPresent (Desc -> Desc
Network.interfaceDFile Desc
homerouterWifiInterfaceOld)
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> IPAddr -> Maybe Gateway -> Property DebianLike
Network.static Desc
homerouterWifiInterface (Desc -> IPAddr
IPv4 Desc
"10.1.1.1") Maybe Gateway
forall a. Maybe a
Nothing
		Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
Network.cleanInterfacesFile
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"hostapd"]
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
"/etc/hostapd/hostapd.conf"
			[ Desc
"interface=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
homerouterWifiInterface
			, Desc
"ssid=house"
			, Desc
"hw_mode=g"
			, Desc
"channel=8"
			]
		Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> Property UnixLike
File.dirExists Desc
"/etc/hostapd"
		Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
"/etc/default/hostapd"
			[ Desc
"DAEMON_CONF=/etc/hostapd/hostapd.conf" ]
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.running Desc
"hostapd"
	Props DebianLike
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.enabled Desc
"hostapd"
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
"/etc/resolv.conf"
		[ Desc
"domain kitenet.net"
		, Desc
"search kitenet.net"
		, Desc
"nameserver 8.8.8.8"
		, Desc
"nameserver 8.8.4.4"
		]
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"dnsmasq"]
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
"/etc/dnsmasq.conf"
		[ Desc
"domain-needed"
		, Desc
"bogus-priv"
		, Desc
"interface=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
homerouterWifiInterface
		, Desc
"interface=eth0"
		, Desc
"domain=kitenet.net"
		-- lease time is short because the house
		-- controller wants to know when clients disconnect
		, Desc
"dhcp-range=10.1.1.100,10.1.1.150,10m"
		, Desc
"no-hosts"
		, Desc
"address=/honeybee.kitenet.net/10.1.1.1"
		, Desc
"address=/house.kitenet.net/10.1.1.1"
		, Desc
"dhcp-host=0c:98:38:80:6a:f9,10.1.1.134,android-kodama"
		]
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> Property DebianLike
Service.restarted Desc
"dnsmasq"
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property DebianLike
ipmasq Desc
homerouterWifiInterface
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> IPAddr -> Maybe Gateway -> [(Desc, Desc)] -> Property DebianLike
Network.static' Desc
"eth0" (Desc -> IPAddr
IPv4 Desc
"192.168.1.100")
		(Gateway -> Maybe Gateway
forall a. a -> Maybe a
Just (IPAddr -> Gateway
Network.Gateway (Desc -> IPAddr
IPv4 Desc
"192.168.1.1")))
		-- When satellite is down, fall back to dialup
		[ (Desc
"pre-up", Desc
"poff -a || true")
		, (Desc
"post-down", Desc
"pon")
		-- ethernet autonegotiation with satellite receiver 
		-- sometimes fails
		, (Desc
"ethernet-autoneg", Desc
"off")
		, (Desc
"link-speed", Desc
"100")
		, (Desc
"link-duplex", Desc
"full")
		]
		Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
Network.cleanInterfacesFile
		Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Desc] -> Property DebianLike
Apt.installed [Desc
"ethtool"]
	Props DebianLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"ppp"]
		Property DebianLike
-> Property UnixLike
-> CombinedType (Property DebianLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
"/etc/ppp/peers/provider"
			[ Desc
"user \"joeyh@arczip.com\""
			, Desc
"connect \"/usr/sbin/chat -v -f /etc/chatscripts/pap -T 3825441\""
			, Desc
"/dev/ttyACM0"
			, Desc
"115200"
			, Desc
"noipdefault"
			, Desc
"defaultroute"
			, Desc
"persist"
			, Desc
"noauth"
			]
		Property DebianLike
-> Property
     (Sing
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> CombinedType
     (Property DebianLike)
     (Property
        (Sing
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Desc -> Context -> Property (HasInfo + UnixLike)
forall c. IsContext c => Desc -> c -> Property (HasInfo + UnixLike)
File.hasPrivContent Desc
"/etc/ppp/pap-secrets" (Desc -> Context
Context Desc
"joeyh@arczip.com")

-- | Enable IP masqerading, on whatever other interfaces come up, besides the
-- provided intif.
ipmasq :: String -> Property DebianLike
ipmasq :: Desc -> Property DebianLike
ipmasq Desc
intif = Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
ifupscript
	[ Desc
"#!/bin/sh"
	, Desc
"INTIF=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
intif
	, Desc
"if [ \"$IFACE\" = $INTIF ] || [ \"$IFACE\" = lo ]; then"
	, Desc
"exit 0"
	, Desc
"fi"
	, Desc
"iptables -F"
	, Desc
"iptables -A FORWARD -i $IFACE -o $INTIF -m state --state ESTABLISHED,RELATED -j ACCEPT"
	, Desc
"iptables -A FORWARD -i $INTIF -o $IFACE -j ACCEPT"
	, Desc
"iptables -t nat -A POSTROUTING -o $IFACE -j MASQUERADE"
	, Desc
"echo 1 > /proc/sys/net/ipv4/ip_forward"
	]
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Desc -> Property UnixLike
scriptmode Desc
ifupscript
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Desc -> Property UnixLike
File.dirExists (Desc -> Desc
takeDirectory Desc
pppupscript)
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
pppupscript
		[ Desc
"#!/bin/sh"
		, Desc
"IFACE=$PPP_IFACE " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
ifupscript
		]
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Desc -> Property UnixLike
scriptmode Desc
pppupscript
	Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Desc] -> Property DebianLike
Apt.installed [Desc
"iptables"]
  where
	ifupscript :: Desc
ifupscript = Desc
"/etc/network/if-up.d/ipmasq"
	pppupscript :: Desc
pppupscript = Desc
"/etc/ppp/ip-up.d/ipmasq"
	scriptmode :: Desc -> Property UnixLike
scriptmode Desc
f = Desc
f Desc -> FileMode -> Property UnixLike
`File.mode` [FileMode] -> FileMode
combineModes ([FileMode]
readModes [FileMode] -> [FileMode] -> [FileMode]
forall a. [a] -> [a] -> [a]
++ [FileMode]
executeModes)

laptopSoftware :: Property DebianLike
laptopSoftware :: Property DebianLike
laptopSoftware = [Desc] -> Property DebianLike
Apt.installed
	[ Desc
"intel-microcode", Desc
"acpi"
	, Desc
"procmeter3", Desc
"xfce4", Desc
"procmeter3", Desc
"unclutter-xfixes"
	, Desc
"mplayer", Desc
"fbreader", Desc
"firefox", Desc
"chromium"
	, Desc
"libdatetime-event-sunrise-perl", Desc
"libtime-duration-perl"
	, Desc
"network-manager", Desc
"network-manager-openvpn-gnome", Desc
"openvpn"
	, Desc
"gtk-redshift", Desc
"powertop"
	, Desc
"gimp", Desc
"gthumb", Desc
"inkscape", Desc
"sozi", Desc
"xzgv", Desc
"hugin"
	, Desc
"mpc", Desc
"mpd", Desc
"ncmpc", Desc
"sonata", Desc
"mpdtoys"
	, Desc
"bsdgames", Desc
"nethack-console"
	, Desc
"xmonad", Desc
"libghc-xmonad-dev", Desc
"libghc-xmonad-contrib-dev"
	, Desc
"ttf-bitstream-vera", Desc
"fonts-symbola", Desc
"fonts-noto-color-emoji"
	, Desc
"mairix", Desc
"offlineimap", Desc
"mutt", Desc
"slrn"
	, Desc
"mtr", Desc
"nmap", Desc
"whois", Desc
"wireshark", Desc
"tcpdump", Desc
"iftop"
	, Desc
"pmount", Desc
"tree", Desc
"pv"
	, Desc
"arbtt", Desc
"hledger", Desc
"bc"
	, Desc
"apache2", Desc
"ikiwiki", Desc
"libhighlight-perl"
	, Desc
"avahi-daemon", Desc
"avahi-discover"
	, Desc
"pal"
	, Desc
"yeahconsole", Desc
"xkbset", Desc
"xinput"
	, Desc
"assword", Desc
"pumpa"
	, Desc
"vorbis-tools", Desc
"audacity"
	, Desc
"ekiga"
	, Desc
"bluez-firmware", Desc
"blueman", Desc
"pulseaudio-module-bluetooth"
	, Desc
"fwupd"
	, Desc
"xul-ext-ublock-origin", Desc
"xul-ext-pdf.js", Desc
"xul-ext-status4evar"
	, Desc
"vim-syntastic", Desc
"vim-fugitive"
	, Desc
"adb", Desc
"gthumb"
	, Desc
"w3m", Desc
"sm", Desc
"weechat"
	, Desc
"borgbackup", Desc
"wipe", Desc
"smartmontools", Desc
"libgfshare-bin"
	, Desc
"units"
	, Desc
"virtualbox", Desc
"virtualbox-guest-additions-iso", Desc
"qemu-kvm"
	]
	Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
baseSoftware
	Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
devSoftware

baseSoftware :: Property DebianLike
baseSoftware :: Property DebianLike
baseSoftware = [Desc] -> Property DebianLike
Apt.installed
	[ Desc
"bash", Desc
"bash-completion", Desc
"vim", Desc
"screen", Desc
"less", Desc
"moreutils"
	, Desc
"git", Desc
"mr", Desc
"etckeeper", Desc
"git-annex", Desc
"ssh", Desc
"vim-vimoutliner"
	]

devSoftware :: Property DebianLike
devSoftware :: Property DebianLike
devSoftware = [Desc] -> Property DebianLike
Apt.installed
	[ Desc
"build-essential", Desc
"debhelper", Desc
"devscripts"
	, Desc
"ghc", Desc
"cabal-install", Desc
"haskell-stack"
	, Desc
"hothasktags", Desc
"hdevtools", Desc
"hlint"
	, Desc
"gdb", Desc
"time"
	, Desc
"dpkg-repack", Desc
"lintian"
	, Desc
"pristine-tar", Desc
"github-backup"
	]

cubieTruckOneWire :: Property DebianLike
cubieTruckOneWire :: Property DebianLike
cubieTruckOneWire = Property UnixLike
utilitysetup
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property UnixLike
dtsinstalled
	Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
utilityinstalled
  where
	dtsinstalled :: CombinedType (Property UnixLike) (Property UnixLike)
dtsinstalled = Desc -> [Desc] -> Property UnixLike
File.hasContent Desc
"/etc/easy-peasy-devicetree-squeezy/my.dts" [Desc]
mydts
		Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> Property UnixLike
File.dirExists Desc
"/etc/easy-peasy-devicetree-squeezy"
	utilityinstalled :: CombinedType (Property DebianLike) (Property DebianLike)
utilityinstalled = User -> Desc -> Desc -> Maybe Desc -> Property DebianLike
Git.cloned (Desc -> User
User Desc
"root") Desc
"https://git.joeyh.name/git/easy-peasy-devicetree-squeezy.git" Desc
"/usr/local/easy-peasy-devicetree-squeezy" Maybe Desc
forall a. Maybe a
Nothing
		Property DebianLike
-> RevertableProperty UnixLike UnixLike
-> CombinedType
     (Property DebianLike) (RevertableProperty UnixLike UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Desc -> LinkTarget -> RevertableProperty UnixLike UnixLike
File.isSymlinkedTo Desc
"/usr/local/bin/easy-peasy-devicetree-squeezy" (Desc -> LinkTarget
File.LinkTarget Desc
"/usr/local/easy-peasy-devicetree-squeezy/easy-peasy-devicetree-squeezy")
		Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Desc] -> Property DebianLike
Apt.installed [Desc
"pv", Desc
"device-tree-compiler", Desc
"cpp", Desc
"linux-source"]
	utilitysetup :: Property UnixLike
utilitysetup = IO Bool -> Property UnixLike -> Property UnixLike
forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Bool -> Bool
not (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Desc -> IO Bool
doesFileExist Desc
dtb) (Property UnixLike -> Property UnixLike)
-> Property UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$ 
		Desc -> [Desc] -> UncheckedProperty UnixLike
cmdProperty Desc
"easy-peasy-devicetree-squeezy"
			[Desc
"--debian", Desc
"sun7i-a20-cubietruck"]
			UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
	dtb :: Desc
dtb = Desc
"/etc/flash-kernel/dtbs/sun7i-a20-cubietruck.dtb"
	mydts :: [Desc]
mydts =
		[ Desc
"/* Device tree addition enabling onewire sensors on CubieTruck GPIO pin PC21 */"
		, Desc
"#include <dt-bindings/gpio/gpio.h>"
		, Desc
""
		, Desc
"/ {"
		, Desc
"\tonewire_device {"
		, Desc
"\t\tcompatible = \"w1-gpio\";"
		, Desc
"\t\tgpios = <&pio 2 21 GPIO_ACTIVE_HIGH>; /* PC21 */"
		, Desc
"\t\tpinctrl-names = \"default\";"
		, Desc
"\t\tpinctrl-0 = <&my_w1_pin>;"
		, Desc
"\t};"
		, Desc
"};"
		, Desc
""
		, Desc
"&pio {"
		, Desc
"\tmy_w1_pin: my_w1_pin@0 {"
		, Desc
"\t\tallwinner,pins = \"PC21\";"
		, Desc
"\t\tallwinner,function = \"gpio_in\";"
		, Desc
"\t};"
		, Desc
"};"
		]

-- My home networked attached storage server.
homeNAS :: Property DebianLike
homeNAS :: Property DebianLike
homeNAS = Desc -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
"home NAS" (Props DebianLike -> Property DebianLike)
-> Props DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"uhubctl"]
	Props DebianLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
"/etc/udev/rules.d/52-startech-hub.rules" Desc -> [Desc] -> Property UnixLike
`File.hasContent`
		[ Desc
"# let users power control startech hub with uhubctl"
		, Desc
"ATTR{idVendor}==\"" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
hubvendor Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"\", ATTR{idProduct}==\"005a\", MODE=\"0666\""
		]
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> USBHubPort -> USBDriveId -> Maybe Desc -> Property DebianLike
autoMountDrivePort Desc
"archive-10"
		(Desc -> Int -> USBHubPort
USBHubPort Desc
hubvendor Int
1)
		(Desc -> Desc -> USBDriveId
USBDriveId Desc
wd Desc
"1230")
		(Desc -> Maybe Desc
forall a. a -> Maybe a
Just Desc
"archive-oldest")
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> USBHubPort -> USBDriveId -> Maybe Desc -> Property DebianLike
autoMountDrivePort Desc
"archive-11"
		(Desc -> Int -> USBHubPort
USBHubPort Desc
hubvendor Int
2)
		(Desc -> Desc -> USBDriveId
USBDriveId Desc
wd Desc
"25ee")
		(Desc -> Maybe Desc
forall a. a -> Maybe a
Just Desc
"archive-older")
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> USBHubPort -> USBDriveId -> Maybe Desc -> Property DebianLike
autoMountDrivePort Desc
"archive-12"
		(Desc -> Int -> USBHubPort
USBHubPort Desc
hubvendor Int
3)
		(Desc -> Desc -> USBDriveId
USBDriveId Desc
seagate Desc
"3322")
		(Desc -> Maybe Desc
forall a. a -> Maybe a
Just Desc
"archive-old")
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> USBHubPort -> USBDriveId -> Maybe Desc -> Property DebianLike
autoMountDrivePort Desc
"archive-13"
		(Desc -> Int -> USBHubPort
USBHubPort Desc
hubvendor Int
4)
		(Desc -> Desc -> USBDriveId
USBDriveId Desc
wd Desc
"25a3")
		(Desc -> Maybe Desc
forall a. a -> Maybe a
Just Desc
"archive")
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc
-> USBHubPort -> USBDriveId -> Maybe Desc -> Property DebianLike
autoMountDrivePort Desc
"archive-14"
		(Desc -> Int -> USBHubPort
USBHubPort Desc
hubvendor Int
2)
		(Desc -> Desc -> USBDriveId
USBDriveId Desc
wd Desc
"25a3")
		Maybe Desc
forall a. Maybe a
Nothing
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Maybe Desc -> Property DebianLike
autoMountDrive Desc
"passport" Maybe Desc
forall a. Maybe a
Nothing
	Props DebianLike
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Property DebianLike
Apt.installed [Desc
"git-annex", Desc
"borgbackup"]
  where
	hubvendor :: Desc
hubvendor = Desc
"0409"
	wd :: Desc
wd = Desc
"1058"
	seagate :: Desc
seagate = Desc
"0bc2"

data USBHubPort = USBHubPort
	{ USBHubPort -> Desc
hubVendor :: String
	, USBHubPort -> Int
hubPort :: Int
	}

data USBDriveId = USBDriveId
	{ USBDriveId -> Desc
driveVendorId :: String
	, USBDriveId -> Desc
driveProductId :: String
	}

-- Makes a USB drive with the given label automount, and unmount after idle
-- for a while.
--
-- The hub port is turned on and off automatically as needed, using
-- uhubctl.
autoMountDrivePort :: Mount.Label -> USBHubPort -> USBDriveId -> Maybe FilePath -> Property DebianLike
autoMountDrivePort :: Desc
-> USBHubPort -> USBDriveId -> Maybe Desc -> Property DebianLike
autoMountDrivePort Desc
label USBHubPort
hp USBDriveId
drive Maybe Desc
malias = Desc -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
desc (Props DebianLike -> Property DebianLike)
-> Props DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> Property UnixLike
File.hasContent (Desc
"/etc/systemd/system/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
hub)
		[ Desc
"[Unit]"
		, Desc
"Description=Startech usb hub port " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Int -> Desc
forall a. Show a => a -> Desc
show (USBHubPort -> Int
hubPort USBHubPort
hp) Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
" vendor " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ USBDriveId -> Desc
driveVendorId USBDriveId
drive Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
" driveid " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ USBDriveId -> Desc
driveProductId USBDriveId
drive
		, Desc
"PartOf=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
mount
		, Desc
"[Service]"
		, Desc
"Type=oneshot"
		, Desc
"RemainAfterExit=true"
		, Desc
"ExecStart=/bin/sh -c 'uhubctl -a on " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
selecthubport Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"'"
		, Desc
"ExecStop=/bin/sh -c 'uhubctl -a off " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
selecthubport
			-- Powering off the port does not remove device
			-- files, so ask udev to remove the devfile; it will
			-- be added back after the drive next spins up
			-- and so avoid mount happening before the drive is
			-- spun up.
			-- (This only works when the devfile is in
			-- by-label.)
			Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"; udevadm trigger --action=remove " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
devfile Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
" || true'"
		, Desc
"[Install]"
		, Desc
"WantedBy="
		]
		Property UnixLike
-> Property Linux
-> CombinedType (Property UnixLike) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property Linux
Systemd.daemonReloaded
	Props Linux
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Desc] -> Desc -> Maybe Desc -> Property DebianLike
autoMountDrive' 
		[ Desc
"Requires=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
hub
		, Desc
"After=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
hub
		] Desc
label Maybe Desc
malias
  where
	devfile :: Desc
devfile = Desc
"/dev/disk/by-label/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
label
	mountpoint :: Desc
mountpoint = Desc
"/media/joey/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
label
	desc :: Desc
desc = Desc
"auto mount with hub port power control " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
mountpoint
	hub :: Desc
hub = Desc
"startech-hub-port-" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Int -> Desc
forall a. Show a => a -> Desc
show (USBHubPort -> Int
hubPort USBHubPort
hp) Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"-vendor-" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ USBDriveId -> Desc
driveVendorId USBDriveId
drive Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"-drivedid-" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ USBDriveId -> Desc
driveProductId USBDriveId
drive Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
".service"
	mount :: Desc
mount = Desc
svcbase Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
".mount"
	svcbase :: Desc
svcbase = Desc -> Desc
Systemd.escapePath Desc
mountpoint
	selecthubport :: Desc
selecthubport = [Desc] -> Desc
unwords
		[ Desc
"-p", Int -> Desc
forall a. Show a => a -> Desc
show (USBHubPort -> Int
hubPort USBHubPort
hp)
		, Desc
"-n", USBHubPort -> Desc
hubVendor USBHubPort
hp
		, Desc
"-l", [Desc] -> Desc
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
			-- The hub's location id, eg "1-1.4", does not seem
			-- as stable as uhubctl claims it will be,
			-- and the vendor is not sufficient since I have 2
			-- hubs from the same vendor. So search for the
			-- drive lsusb to find that. This works even if the
			-- port is powered off, as long as it's been on at
			-- some point before.
			[ Desc
"$(lsusb -tvv | perl -lne \"if (\\\\$h && m!/sys/bus/usb/devices/(.*?) !) {\\\\$v=\\\\$1}; if (m/Hub/) { \\\\$h=1 } else { \\\\$h=0 }; if (/"
			, USBDriveId -> Desc
driveVendorId USBDriveId
drive Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
":" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ USBDriveId -> Desc
driveProductId USBDriveId
drive
			Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
"/) { print \\\\$v; last}\")"
			]
		]

-- Makes a USB drive with the given label automount, and unmount after idle
-- for a while.
autoMountDrive :: Mount.Label -> Maybe FilePath -> Property DebianLike
autoMountDrive :: Desc -> Maybe Desc -> Property DebianLike
autoMountDrive = [Desc] -> Desc -> Maybe Desc -> Property DebianLike
autoMountDrive' []

autoMountDrive' :: [String] -> Mount.Label -> Maybe FilePath -> Property DebianLike
autoMountDrive' :: [Desc] -> Desc -> Maybe Desc -> Property DebianLike
autoMountDrive' [Desc]
mountunitadd Desc
label Maybe Desc
malias = Desc -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
Desc
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList Desc
desc (Props DebianLike -> Property DebianLike)
-> Props DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	Props UnixLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> User -> Group -> Property UnixLike
File.ownerGroup Desc
mountpoint (Desc -> User
User Desc
"joey") (Desc -> Group
Group Desc
"joey")
		Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Desc -> Property UnixLike
File.dirExists Desc
mountpoint
	Props UnixLike
-> RevertableProperty UnixLike UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& case Maybe Desc
malias of
		Just Desc
t -> (Desc
"/media/joey/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
t) Desc -> LinkTarget -> RevertableProperty UnixLike UnixLike
`File.isSymlinkedTo`
			Desc -> LinkTarget
File.LinkTarget Desc
mountpoint
		Maybe Desc
Nothing -> Property UnixLike
forall k (t :: k). SingI t => Property (MetaTypes t)
doNothing Property UnixLike
-> Property UnixLike -> RevertableProperty UnixLike UnixLike
forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> Property UnixLike
forall k (t :: k). SingI t => Property (MetaTypes t)
doNothing
	Props UnixLike
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> Property UnixLike
File.hasContent (Desc
"/etc/systemd/system/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
mount)
		([ Desc
"[Unit]"
		, Desc
"Description=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
label
		] [Desc] -> [Desc] -> [Desc]
forall a. [a] -> [a] -> [a]
++ [Desc]
mountunitadd [Desc] -> [Desc] -> [Desc]
forall a. [a] -> [a] -> [a]
++
		[ Desc
"[Mount]"
		-- avoid mounting whenever the block device is available,
		-- only want to automount on demand
		, Desc
"Options=noauto"
		, Desc
"What=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
devfile
		, Desc
"Where=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
mountpoint
		, Desc
"[Install]"
		, Desc
"WantedBy="
		])
		Property UnixLike
-> Property Linux
-> CombinedType (Property UnixLike) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property Linux
Systemd.daemonReloaded
	Props Linux
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> Property UnixLike
File.hasContent (Desc
"/etc/systemd/system/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
automount)
		[ Desc
"[Unit]"
		, Desc
"Description=Automount " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
label
		, Desc
"[Automount]"
		, Desc
"Where=" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
mountpoint
		, Desc
"TimeoutIdleSec=300"
		, Desc
"[Install]"
		, Desc
"WantedBy=multi-user.target"
		]
		Property UnixLike
-> Property Linux
-> CombinedType (Property UnixLike) (Property Linux)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property Linux
Systemd.daemonReloaded
	Props Linux
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.enabled Desc
automount
	Props Linux
-> Property Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> Property Linux
Systemd.started Desc
automount
	Props Linux
-> RevertableProperty DebianLike Linux
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Desc -> [Desc] -> RevertableProperty DebianLike Linux
Sudo.sudoersDFile (Desc
"automount-" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
label)
		[ Desc
"joey ALL= NOPASSWD: " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
sudocommands
		]
  where
	devfile :: Desc
devfile = Desc
"/dev/disk/by-label/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
label
	mountpoint :: Desc
mountpoint = Desc
"/media/joey/" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
label
	desc :: Desc
desc = Desc
"auto mount " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
mountpoint
	automount :: Desc
automount = Desc
svcbase Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
".automount"
	mount :: Desc
mount = Desc
svcbase Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
".mount"
	svcbase :: Desc
svcbase = Desc -> Desc
Systemd.escapePath Desc
mountpoint
	sudocommands :: Desc
sudocommands = Desc -> [Desc] -> Desc
forall a. [a] -> [[a]] -> [a]
intercalate Desc
" , " ([Desc] -> Desc) -> [Desc] -> Desc
forall a b. (a -> b) -> a -> b
$ (Desc -> Desc) -> [Desc] -> [Desc]
forall a b. (a -> b) -> [a] -> [b]
map (\Desc
c -> Desc
"/bin/systemctl " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
c)
		[ Desc
"stop " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
mountpoint
		, Desc
"start " Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
mountpoint
		]

rsyncNetBorgRepo :: String -> [Borg.BorgRepoOpt] -> Borg.BorgRepo
rsyncNetBorgRepo :: Desc -> [BorgRepoOpt] -> BorgRepo
rsyncNetBorgRepo Desc
d [BorgRepoOpt]
os = [BorgRepoOpt] -> Desc -> BorgRepo
Borg.BorgRepoUsing [BorgRepoOpt]
os' (Desc
"2318@usw-s002.rsync.net:" Desc -> Desc -> Desc
forall a. [a] -> [a] -> [a]
++ Desc
d)
  where
	-- rsync.net has a newer borg here
	os' :: [BorgRepoOpt]
os' = (Desc, Desc) -> BorgRepoOpt
Borg.UsesEnvVar (Desc
"BORG_REMOTE_PATH", Desc
"borg1") BorgRepoOpt -> [BorgRepoOpt] -> [BorgRepoOpt]
forall a. a -> [a] -> [a]
: [BorgRepoOpt]
os

noExim :: Property DebianLike
noExim :: Property DebianLike
noExim = [Desc] -> Property DebianLike
Apt.removed [Desc
"exim4", Desc
"exim4-base", Desc
"exim4-daemon-light"]
	Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
Apt.autoRemove