summaryrefslogtreecommitdiff
path: root/src/Propellor/Property/SiteSpecific/GitAnnexBuilder.hs
blob: a34071ce3d07659dc604a5ca786564608cfb395b (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
{-# 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 = "builder"

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

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

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

type TimeOut = String -- eg, 5h

autobuilder :: Architecture -> Times -> TimeOut -> Property HasInfo
autobuilder arch crontimes timeout = combineProperties "gitannexbuilder" $ props
	& Apt.serviceInstalledRunning "cron"
	& Cron.niceJob "gitannexbuilder" crontimes (User builduser) gitbuilderdir
		("git pull ; timeout " ++ timeout ++ " ./autobuild")
	& rsyncpassword
  where
	context = Context ("gitannexbuilder " ++ arch)
	pwfile = homedir </> "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 = withPrivData (Password builduser) context $ \getpw ->
		property "rsync password" $ getpw $ \pw -> do
			have <- liftIO $ catchDefaultIO "" $
				readFileStrict pwfile
			let want = privDataVal pw
			if want /= have
				then makeChange $ writeFile pwfile want
				else noChange

tree :: Architecture -> Flavor -> Property HasInfo
tree buildarch flavor = combineProperties "gitannexbuilder tree" $ props
	& Apt.installed ["git"]
	& File.dirExists gitbuilderdir
	& File.ownerGroup gitbuilderdir (User builduser) (Group builduser)
	& gitannexbuildercloned
	& builddircloned
  where
	gitannexbuildercloned = check (not <$> (doesDirectoryExist (gitbuilderdir </> ".git"))) $ 
		userScriptProperty (User builduser)
			[ "git clone git://git.kitenet.net/gitannexbuilder " ++ gitbuilderdir
			, "cd " ++ gitbuilderdir
			, "git checkout " ++ buildarch ++ fromMaybe "" flavor
			]
			`assume` MadeChange
			`describe` "gitbuilder setup"
	builddircloned = check (not <$> doesDirectoryExist builddir) $ userScriptProperty (User builduser)
		[ "git clone git://git-annex.branchable.com/ " ++ builddir
		]
		`assume` MadeChange

buildDepsApt :: Property HasInfo
buildDepsApt = combineProperties "gitannexbuilder build deps" $ props
	& Apt.buildDep ["git-annex"]
	& buildDepsNoHaskellLibs
	& Apt.buildDepIn builddir
		`describe` "git-annex source build deps installed"

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

haskellPkgsInstalled :: String -> Property NoInfo
haskellPkgsInstalled dir = flagFile go ("/haskellpkgsinstalled")
  where
	go = userScriptProperty (User builduser)
		[ "cd " ++ builddir ++ " && ./standalone/" ++ dir ++ "/install-haskell-packages"
		]
		`assume` MadeChange

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

autoBuilderContainer :: (System -> Flavor -> Property HasInfo) -> System -> Flavor -> Times -> TimeOut -> Systemd.Container
autoBuilderContainer mkprop osver@(System _ arch) flavor crontime timeout =
	Systemd.container name osver (Chroot.debootstrapped mempty)
		& mkprop osver flavor
		& buildDepsApt
		& autobuilder arch crontime timeout
  where
	name = arch ++ fromMaybe "" flavor ++ "-git-annex-builder"

type Flavor = Maybe String

standardAutoBuilder :: System -> Flavor -> Property HasInfo
standardAutoBuilder osver@(System _ arch) flavor =
	propertyList "standard git-annex autobuilder" $ props
		& os osver
		& Apt.stdSourcesList
		& Apt.unattendedUpgrades
		& User.accountFor (User builduser)
		& tree arch flavor

armAutoBuilder :: System -> Flavor -> Property HasInfo
armAutoBuilder osver flavor = 
	propertyList "arm git-annex autobuilder" $ props
		& standardAutoBuilder osver flavor
		& buildDepsNoHaskellLibs
		-- Works around ghc crash with parallel builds on arm.
		& (homedir </> ".cabal" </> "config")
			`File.lacksLine` "jobs: $ncpus"
		-- Install patched haskell packages for portability to
		-- arm NAS's using old kernel versions.
		& haskellPkgsInstalled "linux"

androidAutoBuilderContainer :: Times -> TimeOut -> Systemd.Container
androidAutoBuilderContainer crontimes timeout =
	androidContainer "android-git-annex-builder" (tree "android" Nothing) builddir
		& Apt.unattendedUpgrades
		& buildDepsNoHaskellLibs
		& autobuilder "android" crontimes timeout

-- Android is cross-built in a Debian i386 container, using the Android NDK.
androidContainer
	:: (IsProp (Property (CInfo NoInfo i)), (Combines (Property NoInfo) (Property i)))
	=> Systemd.MachineName
	-> Property i
	-> FilePath
	-> Systemd.Container
androidContainer name setupgitannexdir gitannexdir = Systemd.container name osver bootstrap
	& Apt.stdSourcesList
	& User.accountFor (User builduser)
	& File.dirExists gitbuilderdir
	& File.ownerGroup homedir (User builduser) (Group builduser)
	& flagFile chrootsetup ("/chrootsetup")
		`requires` setupgitannexdir
	& haskellPkgsInstalled "android"
  where
	-- Use git-annex's android chroot setup script, which will install
	-- ghc-android and the NDK, all build deps, etc, in the home
	-- directory of the builder user.
	chrootsetup = scriptProperty
		[ "cd " ++ gitannexdir ++ " && ./standalone/android/buildchroot-inchroot"
		]
		`assume` MadeChange
	osver = System (Debian (Stable "jessie")) "i386"
	bootstrap = Chroot.debootstrapped mempty