{-# 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 :: UserName
builduser = UserName
"builder"

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

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

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

type TimeOut = String -- eg, 5h

type ArchString = String

autobuilder :: ArchString -> Times -> TimeOut -> Property (HasInfo + DebianLike)
autobuilder :: UserName -> Times -> UserName -> Property (HasInfo + DebianLike)
autobuilder UserName
arch Times
crontimes UserName
timeout = UserName
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
UserName
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties UserName
"gitannexbuilder" (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))
& UserName -> Property DebianLike
Apt.serviceInstalledRunning UserName
"cron"
	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))
& UserName
-> Times -> User -> UserName -> UserName -> Property DebianLike
Cron.niceJob UserName
"gitannexbuilder" Times
crontimes (UserName -> User
User UserName
builduser) UserName
gitbuilderdir
		(UserName
"git pull ; timeout " UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName
timeout UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName
" ./autobuild")
	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)
rsyncpassword
  where
	context :: Context
context = UserName -> Context
Context (UserName
"gitannexbuilder " UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName
arch)
	pwfile :: UserName
pwfile = UserName
homedir UserName -> UserName -> UserName
</> UserName
"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 = PrivDataField
-> Context
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property
         (MetaTypes
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall c s metatypes.
(IsContext c, IsPrivDataSource s,
 IncludesInfo metatypes ~ 'True) =>
s
-> c
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property metatypes)
-> Property metatypes
withPrivData (UserName -> PrivDataField
Password UserName
builduser) Context
context ((((PrivData -> Propellor Result) -> Propellor Result)
  -> Property
       (MetaTypes
          '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property
         (MetaTypes
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ \(PrivData -> Propellor Result) -> Propellor Result
getpw ->
		UserName
-> Propellor Result
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
UserName -> Propellor Result -> Property (MetaTypes metatypes)
property UserName
"rsync password" (Propellor Result
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Propellor Result
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ (PrivData -> Propellor Result) -> Propellor Result
getpw ((PrivData -> Propellor Result) -> Propellor Result)
-> (PrivData -> Propellor Result) -> Propellor Result
forall a b. (a -> b) -> a -> b
$ \PrivData
pw -> do
			UserName
have <- IO UserName -> Propellor UserName
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UserName -> Propellor UserName)
-> IO UserName -> Propellor UserName
forall a b. (a -> b) -> a -> b
$ UserName -> IO UserName -> IO UserName
forall (m :: * -> *) a. MonadCatch m => a -> m a -> m a
catchDefaultIO UserName
"" (IO UserName -> IO UserName) -> IO UserName -> IO UserName
forall a b. (a -> b) -> a -> b
$
				UserName -> IO UserName
readFileStrict UserName
pwfile
			let want :: UserName
want = PrivData -> UserName
privDataVal PrivData
pw
			if UserName
want UserName -> UserName -> Bool
forall a. Eq a => a -> a -> Bool
/= UserName
have
				then IO () -> Propellor Result
makeChange (IO () -> Propellor Result) -> IO () -> Propellor Result
forall a b. (a -> b) -> a -> b
$ UserName -> UserName -> IO ()
writeFile UserName
pwfile UserName
want
				else Propellor Result
noChange

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

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

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

haskellPkgsInstalled :: String -> Property DebianLike
haskellPkgsInstalled :: UserName -> Property DebianLike
haskellPkgsInstalled UserName
dir = 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
$
	Property UnixLike -> UserName -> Property UnixLike
forall i. Property i -> UserName -> Property i
flagFile Property UnixLike
go (UserName
"/haskellpkgsinstalled")
  where
	go :: Property UnixLike
go = User -> [UserName] -> UncheckedProperty UnixLike
userScriptProperty (UserName -> User
User UserName
builduser)
		[ UserName
"cd " UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName
builddir UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName
" && ./standalone/" UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName
dir UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName
"/install-haskell-packages"
		]
		UncheckedProperty UnixLike -> Result -> Property UnixLike
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 = Property UnixLike -> UserName -> Property UnixLike
forall i. Property i -> UserName -> Property i
flagFile Property UnixLike
go UserName
cabalupdated
	where
		go :: Property UnixLike
go = User -> [UserName] -> UncheckedProperty UnixLike
userScriptProperty (UserName -> User
User UserName
builduser)
			[UserName
"cabal update && cabal install git-annex --only-dependencies || true"]
			UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
		cabalupdated :: UserName
cabalupdated = UserName
homedir UserName -> UserName -> UserName
</> UserName
".cabal" UserName -> UserName -> UserName
</> UserName
"packages" UserName -> UserName -> UserName
</> UserName
"hackage.haskell.org" UserName -> UserName -> UserName
</> UserName
"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
-> UserName
-> Container
autoBuilderContainer DebianSuite
-> Architecture -> Flavor -> Property (HasInfo + Debian)
mkprop DebianSuite
suite Architecture
arch Flavor
flavor Times
crontime UserName
timeout =
	UserName -> (UserName -> Chroot) -> Container
Systemd.container UserName
name ((UserName -> Chroot) -> Container)
-> (UserName -> Chroot) -> Container
forall a b. (a -> b) -> a -> b
$ \UserName
d -> DebootstrapConfig
-> UserName
-> Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Chroot
forall metatypes.
DebootstrapConfig -> UserName -> Props metatypes -> Chroot
Chroot.debootstrapped DebootstrapConfig
forall a. Monoid a => a
mempty UserName
d (Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian]) -> Chroot)
-> Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian]) -> Chroot
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		Props UnixLike
-> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian]))
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
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ '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))
& UserName -> Times -> UserName -> Property (HasInfo + DebianLike)
autobuilder (Architecture -> UserName
architectureToDebianArchString Architecture
arch) Times
crontime UserName
timeout
  where
	name :: UserName
name = Architecture -> UserName
architectureToDebianArchString Architecture
arch UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName -> Flavor -> UserName
forall a. a -> Maybe a -> a
fromMaybe UserName
"" Flavor
flavor UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ UserName
"-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 =
	UserName
-> Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
forall k (metatypes :: k).
SingI metatypes =>
UserName
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList UserName
"standard git-annex autobuilder" (Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
 -> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian]))
-> Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		Props UnixLike
-> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian]))
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
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property Debian
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian] '[ 'Targeting 'OSDebian]))
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
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> RevertableProperty DebianLike DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ '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
Apt.unattendedUpgrades
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ '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
Apt.cacheCleaned
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ '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 (UserName -> User
User UserName
builduser)
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ '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))
& UserName -> Flavor -> Property DebianLike
tree (Architecture -> UserName
architectureToDebianArchString Architecture
arch) Flavor
flavor
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property DebianLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ '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
buildDepsApt

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

stackInstalled :: Property DebianLike
stackInstalled :: Property DebianLike
stackInstalled = UserName
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
    -> Maybe System -> Propellor Result)
-> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
UserName
-> (OuterMetaTypesWitness metatypes
    -> Maybe System -> Propellor Result)
-> Property (MetaTypes metatypes)
withOS UserName
"stack installed" ((OuterMetaTypesWitness
    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
  -> Maybe System -> Propellor Result)
 -> Property DebianLike)
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
    -> Maybe System -> Propellor Result)
-> Property DebianLike
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 UserName
"jessie")) Architecture
arch)) ->
			OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Property
     (MetaTypes
        '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux])
-> Propellor Result
forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w (Property
   (MetaTypes
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux])
 -> Propellor Result)
-> Property
     (MetaTypes
        '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux])
-> Propellor Result
forall a b. (a -> b) -> a -> b
$ Architecture
-> Property
     (MetaTypes
        '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux])
manualinstall Architecture
arch
		Maybe System
_ -> OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Property DebianLike -> Propellor Result
forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w (Property DebianLike -> Propellor Result)
-> Property DebianLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ [UserName] -> Property DebianLike
Apt.installed [UserName
"haskell-stack"]
  where
	-- Warning: Using a binary downloaded w/o validation.
	manualinstall :: Architecture -> Property Linux
	manualinstall :: Architecture
-> Property
     (MetaTypes
        '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux])
manualinstall Architecture
arch = Property UnixLike
-> Property
     (MetaTypes
        '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux])
forall (p :: * -> *) (untightened :: [MetaType])
       (tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
 SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property UnixLike
 -> Property
      (MetaTypes
         '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux]))
-> Property UnixLike
-> Property
     (MetaTypes
        '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux])
forall a b. (a -> b) -> a -> b
$ 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
<$> UserName -> IO Bool
doesFileExist UserName
binstack) (Property UnixLike -> Property UnixLike)
-> Property UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$
		UserName -> Props UnixLike -> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
UserName
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList UserName
"stack installed from upstream tarball" (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))
& UserName -> [UserName] -> UncheckedProperty UnixLike
cmdProperty UserName
"wget" [UserName
url, UserName
"-O", UserName
tmptar]
				UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			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))
& UserName -> Property UnixLike
File.dirExists UserName
tmpdir
			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))
& UserName -> [UserName] -> UncheckedProperty UnixLike
cmdProperty UserName
"tar" [UserName
"xf", UserName
tmptar, UserName
"-C", UserName
tmpdir, UserName
"--strip-components=1"]
				UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			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))
& UserName -> [UserName] -> UncheckedProperty UnixLike
cmdProperty UserName
"mv" [UserName
tmpdir UserName -> UserName -> UserName
</> UserName
"stack", UserName
binstack]
				UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			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))
& UserName -> [UserName] -> UncheckedProperty UnixLike
cmdProperty UserName
"rm" [UserName
"-rf", UserName
tmpdir, UserName
tmptar]
				UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
			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))
& case Architecture
arch of
				Architecture
ARMEL -> RevertableProperty UnixLike UnixLike -> Property UnixLike
forall setupmetatypes undometatypes.
RevertableProperty setupmetatypes undometatypes
-> Property setupmetatypes
setupRevertableProperty (RevertableProperty UnixLike UnixLike -> Property UnixLike)
-> RevertableProperty UnixLike UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$
					UserName
"/lib/ld-linux-armhf.so.3"
					UserName -> LinkTarget -> RevertableProperty UnixLike UnixLike
`File.isSymlinkedTo`
					UserName -> LinkTarget
File.LinkTarget UserName
"/lib/ld-linux.so.3"
				Architecture
_ -> Property UnixLike
forall k (t :: k). SingI t => Property (MetaTypes t)
doNothing
	  where
		url :: UserName
url = case Architecture
arch of
			Architecture
X86_32 -> UserName
"https://www.stackage.org/stack/linux-i386"
			Architecture
X86_64 -> UserName
"https://www.stackage.org/stack/linux-x86_64"
			Architecture
ARMEL -> UserName
"https://github.com/commercialhaskell/stack/releases/download/v1.7.1/stack-1.7.1-linux-arm.tar.gz"
			-- Probably not available.
			Architecture
a -> UserName
"https://www.stackage.org/stack/linux-" UserName -> UserName -> UserName
forall a. [a] -> [a] -> [a]
++ Architecture -> UserName
architectureToDebianArchString Architecture
a
	binstack :: UserName
binstack = UserName
"/usr/bin/stack"
	tmptar :: UserName
tmptar = UserName
"/root/stack.tar.gz"
	tmpdir :: UserName
tmpdir = UserName
"/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 =
	UserName
-> Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
forall k (metatypes :: k).
SingI metatypes =>
UserName
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList UserName
"arm git-annex autobuilder" (Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
 -> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian]))
-> Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		Props UnixLike
-> Property (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian]))
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.
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ '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))
& UserName -> Property UnixLike
File.dirExists (UserName
homedir UserName -> UserName -> UserName
</> UserName
".cabal")
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ '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))
& (UserName
homedir UserName -> UserName -> UserName
</> UserName
".cabal" UserName -> UserName -> UserName
</> UserName
"config")
			UserName -> UserName -> Property UnixLike
`File.containsLine` UserName
"jobs: 1"
		-- Work around https://github.com/systemd/systemd/issues/7135
		Props (MetaTypes '[ 'WithInfo, 'Targeting 'OSDebian])
-> RevertableProperty
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux])
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian]
           '[ 'WithInfo, '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))
& UserName
-> RevertableProperty
     (HasInfo
      + MetaTypes
          '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
             'Targeting 'OSArchLinux])
     (HasInfo
      + MetaTypes
          '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
             'Targeting 'OSArchLinux])
Systemd.containerCfg UserName
"--system-call-filter=set_tls"