{-# OPTIONS_HADDOCK prune #-}
{-# LANGUAGE TypeFamilies #-}

{-|
Maintainer: Sean Whitton <spwhitton@spwhitton.name>

Build and maintain schroots for use with sbuild.

For convenience we set up several enhancements, such as ccache and eatmydata.
This means we have to make several assumptions:

1. you want to build for a Debian release strictly newer than squeeze, or for a
Buntish release newer than or equal to trusty

2. if you want to build for Debian stretch or newer, you have sbuild 0.70.0 or
newer

The latter is due to the migration from GnuPG v1 to GnuPG v2.1 in Debian
stretch, which older sbuild can't handle.

Suggested usage in @config.hs@:

>  mybox = host "mybox.example.com" $ props
>  	& osDebian (Stable "bookworm") X86_64
>  	& Apt.useLocalCacher
>  	& sidSchrootBuilt
>  	& Sbuild.usableBy (User "spwhitton")
>  	& Schroot.overlaysInTmpfs
>    where
>  	sidSchrootBuilt = Sbuild.built Sbuild.UseCcache $ props
>  		& osDebian Unstable X86_32
>  		& Sbuild.osDebianStandard
>  		& Sbuild.update `period` Weekly (Just 1)
>  		& Chroot.useHostProxy mybox

If you are using sbuild older than 0.70.0, you also need:

>  & Sbuild.keypairGenerated

To take advantage of the piuparts and autopkgtest support, add to your
@~/.sbuildrc@ (assumes sbuild 0.71.0 or newer):

>  $piuparts_opts = [
>      '--no-eatmydata',
>      '--schroot',
>      '%r-%a-sbuild',
>      '--fail-if-inadequate',
>      ];
>
>  $autopkgtest_root_args = "";
>  $autopkgtest_opts = ["--", "schroot", "%r-%a-sbuild"];

On Debian jessie hosts, you should ensure that sbuild and autopkgtest come from
the same suite.  This is because the autopkgtest binary changed its name between
jessie and stretch.  If you have not installed backports of sbuild or
autopkgtest, you don't need to do anything.  But if you have installed either
package from jessie-backports (with Propellor or otherwise), you should install
the other from jessie-backports, too.

-}

module Propellor.Property.Sbuild (
	-- * Creating and updating sbuild schroots
	UseCcache(..),
	built,
	-- * Properties for use inside sbuild schroots
	update,
	osDebianStandard,
	-- * Global sbuild configuration
	-- blockNetwork,
	keypairGenerated,
	keypairInsecurelyGenerated,
	usableBy,
	userConfig,
) where

import Propellor.Base
import Propellor.Types.Core
import Propellor.Types.Info
import Propellor.Property.Debootstrap (extractSuite)
import qualified Propellor.Property.Apt as Apt
import qualified Propellor.Property.Ccache as Ccache
import qualified Propellor.Property.Chroot as Chroot
import qualified Propellor.Property.ConfFile as ConfFile
import qualified Propellor.Property.Debootstrap as Debootstrap
import qualified Propellor.Property.File as File
-- import qualified Propellor.Property.Firewall as Firewall
import qualified Propellor.Property.Schroot as Schroot
import qualified Propellor.Property.Reboot as Reboot
import qualified Propellor.Property.Localdir as Localdir
import qualified Propellor.Property.User as User

import Data.List

-- | Whether an sbuild schroot should use ccache during builds
--
-- ccache is generally useful but it breaks building some packages.  This data
-- types allows you to toggle it on and off for particular schroots.
data UseCcache = UseCcache | NoCcache

-- | Build and configure a schroot for use with sbuild
--
-- The second parameter should specify, at a minimum, the operating system for
-- the schroot.  This is usually done using a property like 'osDebian'
built
	:: UseCcache
	-> Props metatypes
	-> RevertableProperty (HasInfo + DebianLike) Linux
built :: forall metatypes.
UseCcache
-> Props metatypes
-> RevertableProperty
     (HasInfo
      + MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
     Linux
built UseCcache
cc Props metatypes
ps = case forall metatypes. Props metatypes -> Maybe System
schrootSystem Props metatypes
ps of
	Maybe System
Nothing -> RevertableProperty
  (HasInfo
   + MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
  Linux
emitError
	Just s :: System
s@(System Distribution
_ Architecture
arch) -> case System -> Maybe String
extractSuite System
s of
		Maybe String
Nothing -> RevertableProperty
  (HasInfo
   + MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
  Linux
emitError
		Just String
suite -> forall metatypes.
UseCcache
-> Props metatypes
-> String
-> String
-> RevertableProperty
     (HasInfo
      + MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
     Linux
built' UseCcache
cc Props metatypes
ps String
suite
			(Architecture -> String
architectureToDebianArchString Architecture
arch)
  where
	schrootSystem :: Props metatypes -> Maybe System
	schrootSystem :: forall metatypes. Props metatypes -> Maybe System
schrootSystem (Props [ChildProperty]
ps') = forall v. InfoVal v -> Maybe v
fromInfoVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall v. IsInfo v => Info -> v
fromInfo forall a b. (a -> b) -> a -> b
$
		forall a. Monoid a => [a] -> a
mconcat (forall a b. (a -> b) -> [a] -> [b]
map forall p. IsProp p => p -> Info
getInfo [ChildProperty]
ps')

	emitError :: RevertableProperty (HasInfo + DebianLike) Linux
	emitError :: RevertableProperty
  (HasInfo
   + MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
  Linux
emitError = forall {k} (t :: k). SingI t => String -> Property (MetaTypes t)
impossible String
theError forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> forall {k} (t :: k). SingI t => String -> Property (MetaTypes t)
impossible String
theError
	theError :: String
theError = String
"sbuild schroot does not specify suite and/or architecture"

built'
	:: UseCcache
	-> Props metatypes
	-> String
	-> String
	-> RevertableProperty (HasInfo + DebianLike) Linux
built' :: forall metatypes.
UseCcache
-> Props metatypes
-> String
-> String
-> RevertableProperty
     (HasInfo
      + MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
     Linux
built' UseCcache
cc (Props [ChildProperty]
ps) String
suite String
arch = Property
  (HasInfo
   + MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
provisioned forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> Property Linux
deleted
  where
	provisioned :: Property (HasInfo + DebianLike)
	provisioned :: Property
  (HasInfo
   + MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
provisioned = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties String
desc 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))
& Property UnixLike
cleanupOldConfig
		forall {a} p (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 '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
overlaysKernel
		forall {a} p (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 '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
preReqsInstalled
		forall {a} p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& UseCcache
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
ccacheMaybePrepared UseCcache
cc
		forall {a} p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Chroot -> RevertableProperty (HasInfo + Linux) Linux
Chroot.provisioned Chroot
schroot
		forall {a} p (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
-> Property
     (MetaTypes
        (Combine
           (Combine
              (Combine
                 (Combine
                    (Combine
                       (Combine
                          (Combine
                             (Combine
                                '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                                   'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
                                '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                                   'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                             '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                                'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                          '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                             'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                       '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                          'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                 '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
              '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                 'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
conf String
suite String
arch
	  where
		desc :: String
desc = String
"built sbuild schroot for " forall a. [a] -> [a] -> [a]
++ String
suiteArch

	-- TODO we should kill any sessions still using the chroot
	-- before destroying it (as suggested by sbuild-destroychroot)
	deleted :: Property Linux
	deleted :: Property Linux
deleted = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties String
desc forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		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))
! Chroot -> RevertableProperty (HasInfo + Linux) Linux
Chroot.provisioned Chroot
schroot
		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))
! RevertableProperty UnixLike UnixLike
compatSymlink
		forall {a} p (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.notPresent String
schrootConf
	  where
		desc :: String
desc = String
"no sbuild schroot for " forall a. [a] -> [a] -> [a]
++ String
suiteArch

	conf :: String
-> String
-> Property
     (MetaTypes
        (Combine
           (Combine
              (Combine
                 (Combine
                    (Combine
                       (Combine
                          (Combine
                             (Combine
                                '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                                   'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
                                '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                                   'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                             '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                                'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                          '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                             'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                       '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                          'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
                 '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
              '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
                 'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
conf String
suite' String
arch' = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties String
"sbuild config file" 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 -> Property UnixLike
pair String
"description" (String
suite' forall a. [a] -> [a] -> [a]
++ String
"/" forall a. [a] -> [a] -> [a]
++ String
arch' forall a. [a] -> [a] -> [a]
++ String
" autobuilder")
		forall {a} p (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 -> Property UnixLike
pair String
"groups" String
"root,sbuild"
		forall {a} p (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 -> Property UnixLike
pair String
"root-groups" String
"root,sbuild"
		forall {a} p (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 -> Property UnixLike
pair String
"profile" String
"sbuild"
		forall {a} p (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 -> Property UnixLike
pair String
"type" String
"directory"
		forall {a} p (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 -> Property UnixLike
pair String
"directory" String
schrootRoot
		forall {a} p (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 '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
unionTypeOverlay
		forall {a} p (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
aliasesLine
		forall {a} p (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 -> Property UnixLike
pair String
"command-prefix" (forall a. [a] -> [[a]] -> [a]
intercalate String
"," [String]
commandPrefix)
	  where
		pair :: String -> String -> Property UnixLike
pair String
k String
v = String -> (String, String, String) -> Property UnixLike
ConfFile.containsIniSetting String
schrootConf
			(String
suiteArch forall a. [a] -> [a] -> [a]
++ String
"-sbuild", String
k, String
v)
		unionTypeOverlay :: Property DebianLike
		unionTypeOverlay :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
unionTypeOverlay = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' String
"add union-type = overlay" forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w ->
			Propellor Bool
Schroot.usesOverlays forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
usesOverlays ->
				if Bool
usesOverlays
				then 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 -> String -> Property UnixLike
pair String
"union-type" String
"overlay"
				else Propellor Result
noChange

	compatSymlink :: RevertableProperty UnixLike UnixLike
compatSymlink = String -> LinkTarget -> RevertableProperty UnixLike UnixLike
File.isSymlinkedTo
		(String
"/etc/sbuild/chroot" String -> String -> String
</> String
suiteArch forall a. [a] -> [a] -> [a]
++ String
"-sbuild")
		(String -> LinkTarget
File.LinkTarget String
schrootRoot)

	-- if we're building a sid chroot, add useful aliases
	-- In order to avoid more than one schroot getting the same aliases, we
	-- only do this if the arch of the chroot equals the host arch.
	aliasesLine :: Property UnixLike
	aliasesLine :: Property UnixLike
aliasesLine = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' String
"maybe set aliases line" forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w ->
		String -> String -> Propellor Bool
sidHostArchSchroot String
suite String
arch forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
isSidHostArchSchroot ->
			if Bool
isSidHostArchSchroot
			then forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w forall a b. (a -> b) -> a -> b
$
				String -> (String, String, String) -> Property UnixLike
ConfFile.containsIniSetting String
schrootConf
					( String
suiteArch forall a. [a] -> [a] -> [a]
++ String
"-sbuild"
					, String
"aliases"
					, String
aliases
					)
			else forall (m :: * -> *) a. Monad m => a -> m a
return Result
NoChange

	-- if the user has indicated that this host should use
	-- union-type=overlay schroots, we need to ensure that we have rebooted
	-- to a kernel supporting OverlayFS.  Otherwise, executing sbuild(1)
	-- will fail.
	overlaysKernel :: Property DebianLike
	overlaysKernel :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
overlaysKernel = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' String
"reboot for union-type=overlay" forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w ->
		Propellor Bool
Schroot.usesOverlays forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
usesOverlays ->
			if Bool
usesOverlays
			then 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
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Reboot.toKernelNewerThan String
"3.18"
			else Propellor Result
noChange

	-- clean up config from earlier versions of this module
	cleanupOldConfig :: Property UnixLike
	cleanupOldConfig :: Property UnixLike
cleanupOldConfig =
		forall {k} (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' String
"old sbuild module config cleaned up" forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> do
			forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w forall a b. (a -> b) -> a -> b
$
				forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (String -> IO Bool
doesFileExist String
fstab)
				(String -> String -> Property UnixLike
File.lacksLine String
fstab String
aptCacheLine)
			forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
MonadCatch m =>
m a -> m (Either IOException a)
tryIO forall a b. (a -> b) -> a -> b
$ String -> IO ()
removeDirectoryRecursive String
profile
			forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> IO ()
nukeFile String
schrootPiupartsConf
			-- assume this did nothing
			Propellor Result
noChange
	  where
		fstab :: String
fstab = String
"/etc/schroot/sbuild/fstab"
		profile :: String
profile = String
"/etc/schroot/piuparts"
		schrootPiupartsConf :: String
schrootPiupartsConf = String
"/etc/schroot/chroot.d"
			String -> String -> String
</> String
suiteArch forall a. [a] -> [a] -> [a]
++ String
"-piuparts-propellor"

	-- the schroot itself
	schroot :: Chroot
schroot = forall metatypes.
DebootstrapConfig -> String -> Props metatypes -> Chroot
Chroot.debootstrapped DebootstrapConfig
Debootstrap.BuilddD
			String
schrootRoot (forall metatypes. [ChildProperty] -> Props metatypes
Props [ChildProperty]
schrootProps)
	schrootProps :: [ChildProperty]
schrootProps =
		[ChildProperty]
ps forall a. [a] -> [a] -> [a]
++ [forall p. IsProp p => p -> ChildProperty
toChildProperty forall a b. (a -> b) -> a -> b
$ [String]
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Apt.installed [String
"eatmydata", String
"ccache"]
		-- Drop /usr/local/propellor since build chroots should be
		-- clean.  Note that propellor does not have to install its
		-- build-deps into the chroot, so this is sufficient cleanup
		, forall p. IsProp p => p -> ChildProperty
toChildProperty forall a b. (a -> b) -> a -> b
$ Property UnixLike
Localdir.removed]

	-- static values
	suiteArch :: String
suiteArch = String
suite forall a. [a] -> [a] -> [a]
++ String
"-" forall a. [a] -> [a] -> [a]
++ String
arch
	schrootRoot :: String
schrootRoot = String
"/srv/chroot" String -> String -> String
</> String
suiteArch
	schrootConf :: String
schrootConf = String
"/etc/schroot/chroot.d"
		String -> String -> String
</> String
suiteArch forall a. [a] -> [a] -> [a]
++ String
"-sbuild-propellor"
	aliases :: String
aliases = forall a. [a] -> [[a]] -> [a]
intercalate String
","
		[ String
"sid"
		-- if the user wants to build for experimental, they would use
		-- their sid chroot and sbuild's --extra-repository option to
		-- enable experimental
		, String
"rc-buggy"
		, String
"experimental"
		-- we assume that building for UNRELEASED means building for
		-- unstable
		, String
"UNRELEASED"
		-- the following is for dgit compatibility:
		, String
"UNRELEASED-"
			forall a. [a] -> [a] -> [a]
++ String
arch
			forall a. [a] -> [a] -> [a]
++ String
"-sbuild"
		]
	commandPrefix :: [String]
commandPrefix = case UseCcache
cc of
		UseCcache
UseCcache -> String
"/var/cache/ccache-sbuild/sbuild-setup"forall a. a -> [a] -> [a]
:[String]
base
		UseCcache
_ -> [String]
base
	  where
		base :: [String]
base = [String
"eatmydata"]

-- | Properties that will be wanted in almost any Debian schroot, but not in
-- schroots for other operating systems.
osDebianStandard :: Property Debian
osDebianStandard :: Property Debian
osDebianStandard = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList String
"standard Debian sbuild properties" 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))
& Property Debian
Apt.stdSourcesList

-- | Ensure that an sbuild schroot's packages and apt indexes are updated
--
-- This replaces use of sbuild-update(1).
update :: Property DebianLike
update :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
update = Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Apt.update forall x y. Combines x y => x -> y -> CombinedType x y
`before` Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Apt.upgrade forall x y. Combines x y => x -> y -> CombinedType x y
`before` Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Apt.autoRemove

aptCacheLine :: String
aptCacheLine :: String
aptCacheLine = String
"/var/cache/apt/archives /var/cache/apt/archives none rw,bind 0 0"

-- | Ensure that sbuild and associated utilities are installed
preReqsInstalled :: Property DebianLike
preReqsInstalled :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
preReqsInstalled = [String]
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Apt.installed [String
"piuparts", String
"autopkgtest", String
"lintian", String
"sbuild"]

-- | Add an user to the sbuild group in order to use sbuild
usableBy :: User -> Property DebianLike
usableBy :: User
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
usableBy User
u = User
-> Group
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
User.hasGroup User
u (String -> Group
Group String
"sbuild") forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
preReqsInstalled

-- | Generate the apt keys needed by sbuild
--
-- You only need this if you are using sbuild older than 0.70.0.
keypairGenerated :: Property DebianLike
keypairGenerated :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
keypairGenerated = 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
secKeyFile) forall a b. (a -> b) -> a -> b
$ Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
go
	forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
preReqsInstalled
	-- Work around Debian bug #792100 which is present in Jessie.
	-- Since this is a harmless mkdir, don't actually check the OS
	forall x y. Combines x y => x -> y -> CombinedType x y
`requires` String -> Property UnixLike
File.dirExists String
"/root/.gnupg"
  where
	go :: Property DebianLike
	go :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
go = 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
$
		String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"sbuild-update" [String
"--keygen"]
		forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange

secKeyFile :: FilePath
secKeyFile :: String
secKeyFile = String
"/var/lib/sbuild/apt-keys/sbuild-key.sec"

-- | Generate the apt keys needed by sbuild using a low-quality source of
-- randomness
--
-- Note that any running rngd will be killed; if you are using rngd, you should
-- arrange for it to be restarted after this property has been ensured.  E.g.
--
-- >  & Sbuild.keypairInsecurelyGenerated
-- >  	`onChange` Systemd.started "my-rngd-service"
--
-- Useful on throwaway build VMs.
--
-- You only need this if you are using sbuild older than 0.70.0.
keypairInsecurelyGenerated :: Property DebianLike
keypairInsecurelyGenerated :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
keypairInsecurelyGenerated = 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
secKeyFile) Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
go
  where
	go :: Property DebianLike
	go :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
go = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties String
"sbuild keyring insecurely generated" 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
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Apt.installed [String
"rng-tools"]
		-- If this dir does not exist the sbuild key generation command
		-- will fail; the user might have deleted it to work around
		-- #831462
		forall {a} p (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
"/var/lib/sbuild/apt-keys"
		-- If there is already an rngd process running we have to kill
		-- it, as it might not be feeding to /dev/urandom.  We can't
		-- kill by pid file because that is not guaranteed to be the
		-- default (/var/run/rngd.pid), so we killall
		forall {a} p (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 -> [String] -> UncheckedProperty UnixLike
userScriptProperty (String -> User
User String
"root")
			[ String
"start-stop-daemon -q -K -R 10 -o -n rngd"
			, String
"rngd -r /dev/urandom"
			]
			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))
& Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
keypairGenerated
		-- Kill off the rngd process we spawned
		forall {a} p (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 -> [String] -> UncheckedProperty UnixLike
userScriptProperty (String -> User
User String
"root")
			[String
"kill $(cat /var/run/rngd.pid)"]
			forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange

ccacheMaybePrepared :: UseCcache -> Property DebianLike
ccacheMaybePrepared :: UseCcache
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
ccacheMaybePrepared UseCcache
cc = case UseCcache
cc of
	UseCcache
UseCcache -> Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
ccachePrepared
	UseCcache
NoCcache  -> forall {k} (t :: k). SingI t => Property (MetaTypes t)
doNothing

-- another script from wiki.d.o/sbuild
ccachePrepared :: Property DebianLike
ccachePrepared :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
ccachePrepared = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList String
"sbuild group ccache configured" forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
	-- We only set a limit on the cache if it doesn't already exist, so the
	-- user can override our default limit
	forall {a} p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& 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
"/var/cache/ccache-sbuild")
		(String
-> Limit
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Ccache.hasLimits String
"/var/cache/ccache-sbuild" (String -> Limit
Ccache.MaxSize String
"2G"))
	forall x y. Combines x y => x -> y -> CombinedType x y
`before` Group
-> Limit
-> RevertableProperty
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
     UnixLike
Ccache.hasCache (String -> Group
Group String
"sbuild") Limit
Ccache.NoLimit
	forall {a} p (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
"/etc/schroot/sbuild/fstab" String -> String -> Property UnixLike
`File.containsLine`
	String
"/var/cache/ccache-sbuild /var/cache/ccache-sbuild none rw,bind 0 0"
		forall p. IsProp p => p -> String -> p
`describe` String
"ccache mounted in sbuild schroots"
	forall {a} p (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
"/var/cache/ccache-sbuild/sbuild-setup" String -> [String] -> Property UnixLike
`File.hasContent`
		[ String
"#!/bin/sh"
		, String
""
		, String
"export CCACHE_DIR=/var/cache/ccache-sbuild"
		, String
"export CCACHE_UMASK=002"
		, String
"export CCACHE_COMPRESS=1"
		, String
"unset CCACHE_HARDLINK"
		, String
"export PATH=\"/usr/lib/ccache:$PATH\""
		, String
""
		, String
"exec \"$@\""
		]
	forall {a} p (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 -> FileMode -> Property UnixLike
File.mode String
"/var/cache/ccache-sbuild/sbuild-setup"
		([FileMode] -> FileMode
combineModes ([FileMode]
readModes forall a. [a] -> [a] -> [a]
++ [FileMode]
executeModes))

-- This doesn't seem to work with the current version of sbuild
-- -- | Block network access during builds
-- --
-- -- This is a hack from <https://wiki.debian.org/sbuild> until #802850 and
-- -- #802849 are resolved.
-- blockNetwork :: Property Linux
-- blockNetwork = Firewall.rule Firewall.OUTPUT Firewall.Filter Firewall.DROP
-- 	(Firewall.GroupOwner (Group "sbuild")
-- 	<> Firewall.NotDestination
-- 		[Firewall.IPWithNumMask (IPv4 "127.0.0.1") 8])
-- 	`requires` installed 	-- sbuild group must exist

-- | Maintain recommended ~/.sbuildrc for a user, and adds them to the
-- sbuild group
--
-- You probably want a custom ~/.sbuildrc on your workstation, but
-- this property is handy for quickly setting up build boxes.
--
-- On Debian jessie hosts, you should ensure that sbuild and autopkgtest come
-- from the same suite.  This is because the autopkgtest binary changed its name
-- between jessie and stretch.  If you have not installed backports of sbuild or
-- autopkgtest, you don't need to do anything.  But if you have installed either
-- package from jessie-backports (with Propellor or otherwise), you should
-- install the other from jessie-backports, too.
userConfig :: User -> Property DebianLike
userConfig :: User
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
userConfig user :: User
user@(User String
u) = Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
go
	forall x y. Combines x y => x -> y -> CombinedType x y
`requires` User
-> Property
     (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
usableBy User
user
	forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
preReqsInstalled
  where
	go :: Property DebianLike
	go :: Property
  (MetaTypes '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
go = forall {k} (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' (String
"~/.sbuildrc for " forall a. [a] -> [a] -> [a]
++ String
u) forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w -> do
		String
h <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (User -> IO String
User.homedir User
user)
		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 -> [String] -> Property UnixLike
File.hasContent (String
h String -> String -> String
</> String
".sbuildrc")
			[ String
"$run_lintian = 1;"
			, String
""
			, String
"$run_piuparts = 1;"
			, String
"$piuparts_opts = ["
			, String
"    '--no-eatmydata',"
			, String
"    '--schroot',"
			, String
"    '%r-%a-sbuild',"
			, String
"    '--fail-if-inadequate',"
			, String
"    ];"
			, String
""
			, String
"$run_autopkgtest = 1;"
			, String
"$autopkgtest_root_args = \"\";"
			, String
"$autopkgtest_opts = [\"--\", \"schroot\", \"%r-%a-sbuild\"];"
			]

-- ==== utility functions ====

-- Determine whether a schroot is
--
-- (i)  Debian sid, and
-- (ii) the same architecture as the host.
--
-- This is the "sid host arch schroot".  It is considered the default schroot
-- for sbuild builds, so we add useful aliases that work well with the suggested
-- ~/.sbuildrc given in the haddock
sidHostArchSchroot :: String -> String -> Propellor Bool
sidHostArchSchroot :: String -> String -> Propellor Bool
sidHostArchSchroot String
suite String
arch = do
	Maybe System
maybeOS <- Propellor (Maybe System)
getOS
	forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Maybe System
maybeOS of
		Maybe System
Nothing -> Bool
False
		Just (System Distribution
_ Architecture
hostArch) ->
			let hostArch' :: String
hostArch' = Architecture -> String
architectureToDebianArchString Architecture
hostArch
			in String
suite forall a. Eq a => a -> a -> Bool
== String
"unstable" Bool -> Bool -> Bool
&& String
hostArch' forall a. Eq a => a -> a -> Bool
== String
arch