{-# LANGUAGE FlexibleContexts #-}

module Propellor.Property.SiteSpecific.GitAnnexBuilder where

import Propellor.Base
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.User as User
import qualified Propellor.Property.Cron as Cron
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Systemd as Systemd
import qualified Propellor.Property.Chroot as Chroot
import Propellor.Property.Cron (Times)

builduser :: UserName
builduser :: String
builduser = String
"builder"

homedir :: FilePath
homedir :: String
homedir = String
"/home/builder"

gitbuilderdir :: FilePath
gitbuilderdir :: String
gitbuilderdir = String
homedir String -> String -> String
</> String
"gitbuilder"

builddir :: FilePath
builddir :: String
builddir = String
gitbuilderdir String -> String -> String
</> String
"build"

type TimeOut = String -- eg, 5h

type ArchString = String

autobuilder :: ArchString -> Times -> TimeOut -> Property (HasInfo + DebianLike)
autobuilder :: String -> Times -> String -> Property (HasInfo + DebianLike)
autobuilder String
arch Times
crontimes String
timeout = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties String
"gitannexbuilder" forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	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))
& String -> Property DebianLike
Apt.serviceInstalledRunning String
"cron"
	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))
& String -> Times -> User -> String -> String -> Property DebianLike
Cron.niceJob String
"gitannexbuilder" Times
crontimes (String -> User
User String
builduser) String
gitbuilderdir
		(String
"git pull ; timeout " forall a. [a] -> [a] -> [a]
++ String
timeout forall a. [a] -> [a] -> [a]
++ String
" ./autobuild")
	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 (HasInfo + DebianLike)
rsyncpassword
  where
	context :: Context
context = String -> Context
Context (String
"gitannexbuilder " forall a. [a] -> [a] -> [a]
++ String
arch)
	pwfile :: String
pwfile = String
homedir String -> String -> String
</> String
"rsyncpassword"
	-- The builduser account does not have a password set,
	-- instead use the password privdata to hold the rsync server
	-- password used to upload the built image.
	rsyncpassword :: Property (HasInfo + DebianLike)
	rsyncpassword :: Property (HasInfo + DebianLike)
rsyncpassword = forall c s metatypes.
(IsContext c, IsPrivDataSource s,
 IncludesInfo metatypes ~ 'True) =>
s
-> c
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property metatypes)
-> Property metatypes
withPrivData (String -> PrivDataField
Password String
builduser) Context
context forall a b. (a -> b) -> a -> b
$ \(PrivData -> Propellor Result) -> Propellor Result
getpw ->
		forall {k} (metatypes :: k).
SingI metatypes =>
String -> Propellor Result -> Property (MetaTypes metatypes)
property String
"rsync password" forall a b. (a -> b) -> a -> b
$ (PrivData -> Propellor Result) -> Propellor Result
getpw forall a b. (a -> b) -> a -> b
$ \PrivData
pw -> do
			String
have <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadCatch m => a -> m a -> m a
catchDefaultIO String
"" forall a b. (a -> b) -> a -> b
$
				String -> IO String
readFileStrict String
pwfile
			let want :: String
want = PrivData -> String
privDataVal PrivData
pw
			if String
want forall a. Eq a => a -> a -> Bool
/= String
have
				then IO () -> Propellor Result
makeChange forall a b. (a -> b) -> a -> b
$ String -> String -> IO ()
writeFile String
pwfile String
want
				else Propellor Result
noChange

tree :: ArchString -> Flavor -> Property DebianLike
tree :: String -> Flavor -> Property DebianLike
tree String
buildarch Flavor
flavor = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties String
"gitannexbuilder tree" forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	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))
& [String] -> Property DebianLike
Apt.installed [String
"git"]
	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))
& String -> Property UnixLike
File.dirExists String
gitbuilderdir
	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))
& String -> User -> Group -> Property UnixLike
File.ownerGroup String
gitbuilderdir (String -> User
User String
builduser) (String -> Group
Group String
builduser)
	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
gitannexbuildercloned
	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
builddircloned
  where
	gitannexbuildercloned :: Property UnixLike
gitannexbuildercloned = forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> IO Bool
doesDirectoryExist (String
gitbuilderdir String -> String -> String
</> String
".git"))) forall a b. (a -> b) -> a -> b
$
		User -> [String] -> UncheckedProperty UnixLike
userScriptProperty (String -> User
User String
builduser)
			[ String
"git clone git://git.kitenet.net/gitannexbuilder " forall a. [a] -> [a] -> [a]
++ String
gitbuilderdir
			, String
"cd " forall a. [a] -> [a] -> [a]
++ String
gitbuilderdir
			, String
"git checkout " forall a. [a] -> [a] -> [a]
++ String
buildarch forall a. [a] -> [a] -> [a]
++ forall a. a -> Maybe a -> a
fromMaybe String
"" Flavor
flavor
			]
			forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			forall p. IsProp p => p -> String -> p
`describe` String
"gitbuilder setup"
	builddircloned :: Property UnixLike
builddircloned = forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Bool
doesDirectoryExist String
builddir) forall a b. (a -> b) -> a -> b
$ User -> [String] -> UncheckedProperty UnixLike
userScriptProperty (String -> User
User String
builduser)
		[ String
"git clone git://git-annex.branchable.com/ " forall a. [a] -> [a] -> [a]
++ String
builddir
		]

buildDepsApt :: Property DebianLike
buildDepsApt :: Property DebianLike
buildDepsApt = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties String
"gitannexbuilder build deps" forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	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))
& [String] -> Property DebianLike
Apt.buildDep [String
"git-annex"]
	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
buildDepsNoHaskellLibs
	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))
& String -> Property DebianLike
Apt.buildDepIn String
builddir
		forall p. IsProp p => p -> String -> p
`describe` String
"git-annex source build deps installed"

buildDepsNoHaskellLibs :: Property DebianLike
buildDepsNoHaskellLibs :: Property DebianLike
buildDepsNoHaskellLibs = [String] -> Property DebianLike
Apt.installed
	[String
"git", String
"rsync", String
"moreutils", String
"ca-certificates",
	String
"debhelper", String
"ghc", String
"curl", String
"openssh-client", String
"git-remote-gcrypt",
	String
"liblockfile-simple-perl", String
"locales", String
"cabal-install", String
"vim", String
"less",
	-- needed by haskell libs
	String
"libxml2-dev", String
"libidn11-dev", String
"libgsasl7-dev", String
"libgnutls28-dev",
	String
"libmagic-dev", String
"alex", String
"happy", String
"c2hs"
	]

haskellPkgsInstalled :: String -> Property DebianLike
haskellPkgsInstalled :: String -> Property DebianLike
haskellPkgsInstalled String
dir = forall (p :: * -> *) (untightened :: [MetaType])
       (tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
 SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets forall a b. (a -> b) -> a -> b
$
	forall i. Property i -> String -> Property i
flagFile Property UnixLike
go (String
"/haskellpkgsinstalled")
  where
	go :: Property UnixLike
go = User -> [String] -> UncheckedProperty UnixLike
userScriptProperty (String -> User
User String
builduser)
		[ String
"cd " forall a. [a] -> [a] -> [a]
++ String
builddir forall a. [a] -> [a] -> [a]
++ String
" && ./standalone/" forall a. [a] -> [a] -> [a]
++ String
dir forall a. [a] -> [a] -> [a]
++ String
"/install-haskell-packages"
		]
		forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange

-- Installs current versions of git-annex's deps from cabal, but only
-- does so once.
cabalDeps :: Property UnixLike
cabalDeps :: Property UnixLike
cabalDeps = forall i. Property i -> String -> Property i
flagFile Property UnixLike
go String
cabalupdated
	where
		go :: Property UnixLike
go = User -> [String] -> UncheckedProperty UnixLike
userScriptProperty (String -> User
User String
builduser)
			[String
"cabal update && cabal install git-annex --only-dependencies || true"]
			forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
		cabalupdated :: String
cabalupdated = String
homedir String -> String -> String
</> String
".cabal" String -> String -> String
</> String
"packages" String -> String -> String
</> String
"hackage.haskell.org" String -> String -> String
</> String
"00-index.cache"

autoBuilderContainer :: (DebianSuite -> Architecture -> Flavor -> Property (HasInfo + Debian)) -> DebianSuite -> Architecture -> Flavor -> Times -> TimeOut -> Systemd.Container
autoBuilderContainer :: (DebianSuite
 -> Architecture -> Flavor -> Property (HasInfo + Debian))
-> DebianSuite
-> Architecture
-> Flavor
-> Times
-> String
-> Container
autoBuilderContainer DebianSuite
-> Architecture -> Flavor -> Property (HasInfo + Debian)
mkprop DebianSuite
suite Architecture
arch Flavor
flavor Times
crontime String
timeout =
	String -> (String -> Chroot) -> Container
Systemd.container String
name forall a b. (a -> b) -> a -> b
$ \String
d -> forall metatypes.
DebootstrapConfig -> String -> Props metatypes -> Chroot
Chroot.debootstrapped forall a. Monoid a => a
mempty String
d forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		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))
& DebianSuite
-> Architecture -> Flavor -> Property (HasInfo + Debian)
mkprop DebianSuite
suite Architecture
arch Flavor
flavor
		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))
& String -> Times -> String -> Property (HasInfo + DebianLike)
autobuilder (Architecture -> String
architectureToDebianArchString Architecture
arch) Times
crontime String
timeout
  where
	name :: String
name = Architecture -> String
architectureToDebianArchString Architecture
arch forall a. [a] -> [a] -> [a]
++ forall a. a -> Maybe a -> a
fromMaybe String
"" Flavor
flavor forall a. [a] -> [a] -> [a]
++ String
"-git-annex-builder"

type Flavor = Maybe String

standardAutoBuilder :: DebianSuite -> Architecture -> Flavor -> Property (HasInfo + Debian)
standardAutoBuilder :: DebianSuite
-> Architecture -> Flavor -> Property (HasInfo + Debian)
standardAutoBuilder DebianSuite
suite Architecture
arch Flavor
flavor =
	forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList String
"standard git-annex autobuilder" forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		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))
& DebianSuite -> Architecture -> Property (HasInfo + Debian)
osDebian DebianSuite
suite Architecture
arch
		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 Debian
Apt.stdSourcesList
		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
Apt.unattendedUpgrades
		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
Apt.cacheCleaned
		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 (String -> User
User String
builduser)
		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))
& String -> Flavor -> Property DebianLike
tree (Architecture -> String
architectureToDebianArchString Architecture
arch) Flavor
flavor
		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
buildDepsApt

stackAutoBuilder :: DebianSuite -> Architecture -> Flavor -> Property (HasInfo + Debian)
stackAutoBuilder :: DebianSuite
-> Architecture -> Flavor -> Property (HasInfo + Debian)
stackAutoBuilder DebianSuite
suite Architecture
arch Flavor
flavor =
	forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList String
"git-annex autobuilder using stack" forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		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))
& DebianSuite -> Architecture -> Property (HasInfo + Debian)
osDebian DebianSuite
suite Architecture
arch
		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
buildDepsNoHaskellLibs
		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 Debian
Apt.stdSourcesList
		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
Apt.unattendedUpgrades
		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
Apt.cacheCleaned
		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 (String -> User
User String
builduser)
		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))
& String -> Flavor -> Property DebianLike
tree (Architecture -> String
architectureToDebianArchString Architecture
arch) Flavor
flavor
		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
stackInstalled
		-- Workaround https://github.com/commercialhaskell/stack/issues/2093
		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))
& [String] -> Property DebianLike
Apt.installed [String
"libtinfo-dev"]

stackInstalled :: Property DebianLike
stackInstalled :: Property DebianLike
stackInstalled = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes
    -> Maybe System -> Propellor Result)
-> Property (MetaTypes metatypes)
withOS String
"stack installed" forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w Maybe System
o ->
	case Maybe System
o of
		(Just (System (Debian DebianKernel
Linux (Stable String
"jessie")) Architecture
arch)) ->
			forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w forall a b. (a -> b) -> a -> b
$ Architecture -> Property Linux
manualinstall Architecture
arch
		Maybe System
_ -> forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w forall a b. (a -> b) -> a -> b
$ [String] -> Property DebianLike
Apt.installed [String
"haskell-stack"]
  where
	-- Warning: Using a binary downloaded w/o validation.
	manualinstall :: Architecture -> Property Linux
	manualinstall :: Architecture -> Property Linux
manualinstall Architecture
arch = forall (p :: * -> *) (untightened :: [MetaType])
       (tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
 SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets forall a b. (a -> b) -> a -> b
$ forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Bool
doesFileExist String
binstack) forall a b. (a -> b) -> a -> b
$
		forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList String
"stack installed from upstream tarball" forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
			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))
& String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"wget" [String
url, String
"-O", String
tmptar]
				forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			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))
& String -> Property UnixLike
File.dirExists String
tmpdir
			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))
& String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"tar" [String
"xf", String
tmptar, String
"-C", String
tmpdir, String
"--strip-components=1"]
				forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			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))
& String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"mv" [String
tmpdir String -> String -> String
</> String
"stack", String
binstack]
				forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			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))
& String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"rm" [String
"-rf", String
tmpdir, String
tmptar]
				forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			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 Architecture
arch of
				Architecture
ARMEL -> forall setupmetatypes undometatypes.
RevertableProperty setupmetatypes undometatypes
-> Property setupmetatypes
setupRevertableProperty forall a b. (a -> b) -> a -> b
$
					String
"/lib/ld-linux-armhf.so.3"
					String -> LinkTarget -> RevertableProperty UnixLike UnixLike
`File.isSymlinkedTo`
					String -> LinkTarget
File.LinkTarget String
"/lib/ld-linux.so.3"
				Architecture
_ -> forall {k} (t :: k). SingI t => Property (MetaTypes t)
doNothing
	  where
		url :: String
url = case Architecture
arch of
			Architecture
X86_32 -> String
"https://www.stackage.org/stack/linux-i386"
			Architecture
X86_64 -> String
"https://www.stackage.org/stack/linux-x86_64"
			Architecture
ARMEL -> String
"https://github.com/commercialhaskell/stack/releases/download/v1.7.1/stack-1.7.1-linux-arm.tar.gz"
			-- Probably not available.
			Architecture
a -> String
"https://www.stackage.org/stack/linux-" forall a. [a] -> [a] -> [a]
++ Architecture -> String
architectureToDebianArchString Architecture
a
	binstack :: String
binstack = String
"/usr/bin/stack"
	tmptar :: String
tmptar = String
"/root/stack.tar.gz"
	tmpdir :: String
tmpdir = String
"/root/stack"

armAutoBuilder :: (DebianSuite -> Architecture -> Flavor -> Property (HasInfo + Debian)) -> DebianSuite -> Architecture -> Flavor -> Property (HasInfo + Debian)
armAutoBuilder :: (DebianSuite
 -> Architecture -> Flavor -> Property (HasInfo + Debian))
-> DebianSuite
-> Architecture
-> Flavor
-> Property (HasInfo + Debian)
armAutoBuilder DebianSuite
-> Architecture -> Flavor -> Property (HasInfo + Debian)
baseautobuilder DebianSuite
suite Architecture
arch Flavor
flavor =
	forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList String
"arm git-annex autobuilder" forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		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))
& DebianSuite
-> Architecture -> Flavor -> Property (HasInfo + Debian)
baseautobuilder DebianSuite
suite Architecture
arch Flavor
flavor
		-- Works around ghc crash with parallel builds on arm.
		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))
& String -> Property UnixLike
File.dirExists (String
homedir String -> String -> String
</> String
".cabal")
		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))
& String -> User -> Group -> Property UnixLike
File.ownerGroup (String
homedir String -> String -> String
</> String
".cabal") (String -> User
User String
"builder") (String -> Group
Group String
"builder")
		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))
& (String
homedir String -> String -> String
</> String
".cabal" String -> String -> String
</> String
"config")
			String -> String -> Property UnixLike
`File.containsLine` String
"jobs: 1"
		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))
& String -> User -> Group -> Property UnixLike
File.ownerGroup (String
homedir String -> String -> String
</> String
".cabal" String -> String -> String
</> String
"config") (String -> User
User String
"builder") (String -> Group
Group String
"builder")
		-- Work around https://github.com/systemd/systemd/issues/7135
		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))
& String -> RevertableProperty (HasInfo + Linux) (HasInfo + Linux)
Systemd.containerCfg String
"--system-call-filter=set_tls"