{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Propellor.Property.Apt where
import Data.Maybe
import Data.List
import Data.Typeable
import System.IO
import Control.Monad
import Control.Applicative
import Prelude
import Propellor.Base
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Service as Service
import Propellor.Property.File (Line)
import Propellor.Types.Info
import Utility.SafeCommand
data HostMirror = HostMirror Url
deriving (HostMirror -> HostMirror -> Bool
(HostMirror -> HostMirror -> Bool)
-> (HostMirror -> HostMirror -> Bool) -> Eq HostMirror
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HostMirror -> HostMirror -> Bool
$c/= :: HostMirror -> HostMirror -> Bool
== :: HostMirror -> HostMirror -> Bool
$c== :: HostMirror -> HostMirror -> Bool
Eq, Int -> HostMirror -> ShowS
[HostMirror] -> ShowS
HostMirror -> String
(Int -> HostMirror -> ShowS)
-> (HostMirror -> String)
-> ([HostMirror] -> ShowS)
-> Show HostMirror
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HostMirror] -> ShowS
$cshowList :: [HostMirror] -> ShowS
show :: HostMirror -> String
$cshow :: HostMirror -> String
showsPrec :: Int -> HostMirror -> ShowS
$cshowsPrec :: Int -> HostMirror -> ShowS
Show, Typeable)
data HostAptProxy = HostAptProxy Url
deriving (HostAptProxy -> HostAptProxy -> Bool
(HostAptProxy -> HostAptProxy -> Bool)
-> (HostAptProxy -> HostAptProxy -> Bool) -> Eq HostAptProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HostAptProxy -> HostAptProxy -> Bool
$c/= :: HostAptProxy -> HostAptProxy -> Bool
== :: HostAptProxy -> HostAptProxy -> Bool
$c== :: HostAptProxy -> HostAptProxy -> Bool
Eq, Int -> HostAptProxy -> ShowS
[HostAptProxy] -> ShowS
HostAptProxy -> String
(Int -> HostAptProxy -> ShowS)
-> (HostAptProxy -> String)
-> ([HostAptProxy] -> ShowS)
-> Show HostAptProxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HostAptProxy] -> ShowS
$cshowList :: [HostAptProxy] -> ShowS
show :: HostAptProxy -> String
$cshow :: HostAptProxy -> String
showsPrec :: Int -> HostAptProxy -> ShowS
$cshowsPrec :: Int -> HostAptProxy -> ShowS
Show, Typeable)
mirror :: Url -> Property (HasInfo + UnixLike)
mirror :: String -> Property (HasInfo + UnixLike)
mirror String
u = String -> InfoVal HostMirror -> Property (HasInfo + UnixLike)
forall v. IsInfo v => String -> v -> Property (HasInfo + UnixLike)
pureInfoProperty (String
u String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" apt mirror selected")
(HostMirror -> InfoVal HostMirror
forall v. v -> InfoVal v
InfoVal (String -> HostMirror
HostMirror String
u))
getMirror :: Propellor Url
getMirror :: Propellor String
getMirror = do
Maybe HostMirror
mirrorInfo <- Propellor (Maybe HostMirror)
getMirrorInfo
Maybe System
osInfo <- Propellor (Maybe System)
getOS
String -> Propellor String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Propellor String) -> String -> Propellor String
forall a b. (a -> b) -> a -> b
$ case (Maybe System
osInfo, Maybe HostMirror
mirrorInfo) of
(Maybe System
_, Just (HostMirror String
u)) -> String
u
(Just (System (Debian DebianKernel
_ DebianSuite
_) Architecture
_), Maybe HostMirror
_) ->
String
"http://deb.debian.org/debian"
(Just (System (Buntish String
_) Architecture
_), Maybe HostMirror
_) ->
String
"mirror://mirrors.ubuntu.com/"
(Just (System Distribution
dist Architecture
_), Maybe HostMirror
_) ->
ShowS
forall a. HasCallStack => String -> a
error (String
"no Apt mirror defined for " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Distribution -> String
forall a. Show a => a -> String
show Distribution
dist)
(Maybe System, Maybe HostMirror)
_ -> ShowS
forall a. HasCallStack => String -> a
error String
"no Apt mirror defined for this host or OS"
where
getMirrorInfo :: Propellor (Maybe HostMirror)
getMirrorInfo :: Propellor (Maybe HostMirror)
getMirrorInfo = InfoVal HostMirror -> Maybe HostMirror
forall v. InfoVal v -> Maybe v
fromInfoVal (InfoVal HostMirror -> Maybe HostMirror)
-> Propellor (InfoVal HostMirror) -> Propellor (Maybe HostMirror)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Propellor (InfoVal HostMirror)
forall v. IsInfo v => Propellor v
askInfo
withMirror :: Desc -> (Url -> Property DebianLike) -> Property DebianLike
withMirror :: String -> (String -> Property DebianLike) -> Property DebianLike
withMirror String
desc String -> Property DebianLike
mkp = String
-> (OuterMetaTypesWitness
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Propellor Result)
-> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' String
desc ((OuterMetaTypesWitness
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Propellor Result)
-> Property DebianLike)
-> (OuterMetaTypesWitness
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Propellor Result)
-> Property DebianLike
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
w -> do
String
u <- Propellor String
getMirror
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 (String -> Property DebianLike
mkp String
u)
sourcesList :: FilePath
sourcesList :: String
sourcesList = String
"/etc/apt/sources.list"
type Url = String
type Section = String
type SourcesGenerator = DebianSuite -> [Line]
showSuite :: DebianSuite -> String
showSuite :: DebianSuite -> String
showSuite (Stable String
s) = String
s
showSuite DebianSuite
Testing = String
"testing"
showSuite DebianSuite
Unstable = String
"unstable"
showSuite DebianSuite
Experimental = String
"experimental"
backportSuite :: DebianSuite -> Maybe String
backportSuite :: DebianSuite -> Maybe String
backportSuite (Stable String
s) = String -> Maybe String
forall a. a -> Maybe a
Just (String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-backports")
backportSuite DebianSuite
_ = Maybe String
forall a. Maybe a
Nothing
stableUpdatesSuite :: DebianSuite -> Maybe String
stableUpdatesSuite :: DebianSuite -> Maybe String
stableUpdatesSuite (Stable String
s) = String -> Maybe String
forall a. a -> Maybe a
Just (String
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-updates")
stableUpdatesSuite DebianSuite
_ = Maybe String
forall a. Maybe a
Nothing
debLine :: String -> Url -> [Section] -> Line
debLine :: String -> String -> [String] -> String
debLine String
suite String
url [String]
sections = [String] -> String
unwords ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$
[String
"deb", String
url, String
suite] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
sections
srcLine :: Line -> Line
srcLine :: ShowS
srcLine String
l = case String -> [String]
words String
l of
(String
"deb":[String]
rest) -> [String] -> String
unwords ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String
"deb-src" String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
rest
[String]
_ -> String
""
stdSections :: [Section]
stdSections :: [String]
stdSections = [String
"main", String
"contrib", String
"non-free"]
binandsrc :: String -> SourcesGenerator
binandsrc :: String -> SourcesGenerator
binandsrc String
url DebianSuite
suite = [Maybe String] -> [String]
forall a. [Maybe a] -> [a]
catMaybes
[ String -> Maybe String
forall a. a -> Maybe a
Just String
l
, String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ ShowS
srcLine String
l
, Maybe String
sul
, ShowS
srcLine ShowS -> Maybe String -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
sul
, Maybe String
bl
, ShowS
srcLine ShowS -> Maybe String -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
bl
]
where
l :: String
l = String -> String -> [String] -> String
debLine (DebianSuite -> String
showSuite DebianSuite
suite) String
url [String]
stdSections
bl :: Maybe String
bl = do
String
bs <- DebianSuite -> Maybe String
backportSuite DebianSuite
suite
String -> Maybe String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ String -> String -> [String] -> String
debLine String
bs String
url [String]
stdSections
sul :: Maybe String
sul = do
String
sus <- DebianSuite -> Maybe String
stableUpdatesSuite DebianSuite
suite
String -> Maybe String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ String -> String -> [String] -> String
debLine String
sus String
url [String]
stdSections
stdArchiveLines :: Propellor SourcesGenerator
stdArchiveLines :: Propellor SourcesGenerator
stdArchiveLines = SourcesGenerator -> Propellor SourcesGenerator
forall (m :: * -> *) a. Monad m => a -> m a
return (SourcesGenerator -> Propellor SourcesGenerator)
-> (String -> SourcesGenerator)
-> String
-> Propellor SourcesGenerator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> SourcesGenerator
binandsrc (String -> Propellor SourcesGenerator)
-> Propellor String -> Propellor SourcesGenerator
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Propellor String
getMirror
securityUpdates :: SourcesGenerator
securityUpdates :: SourcesGenerator
securityUpdates DebianSuite
suite
| DebianSuite -> Bool
isStable DebianSuite
suite =
let l :: String
l = String
"deb http://security.debian.org/debian-security " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
securitysuite String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
stdSections
in [String
l, ShowS
srcLine String
l]
| Bool
otherwise = []
where
securitysuite :: String
securitysuite
| DebianSuite
suite DebianSuite -> [DebianSuite] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String -> DebianSuite) -> [String] -> [DebianSuite]
forall a b. (a -> b) -> [a] -> [b]
map String -> DebianSuite
Stable [String]
releasesusingoldname =
DebianSuite -> String
showSuite DebianSuite
suite String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"/updates"
| Bool
otherwise = DebianSuite -> String
showSuite DebianSuite
suite String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"-security"
releasesusingoldname :: [String]
releasesusingoldname = [String
"jessie", String
"buster", String
"stretch"]
stdSourcesList :: Property Debian
stdSourcesList :: Property Debian
stdSourcesList = String
-> (OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
-> Maybe System -> Propellor Result)
-> Property Debian
forall k (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes
-> Maybe System -> Propellor Result)
-> Property (MetaTypes metatypes)
withOS String
"standard sources.list" ((OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
-> Maybe System -> Propellor Result)
-> Property Debian)
-> (OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
-> Maybe System -> Propellor Result)
-> Property Debian
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
w Maybe System
o -> case Maybe System
o of
(Just (System (Debian DebianKernel
_ DebianSuite
suite) Architecture
_)) ->
OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
-> Property Debian -> Propellor Result
forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
w (Property Debian -> Propellor Result)
-> Property Debian -> Propellor Result
forall a b. (a -> b) -> a -> b
$ DebianSuite -> Property Debian
stdSourcesListFor DebianSuite
suite
Maybe System
_ -> Propellor Result
HasCallStack => Propellor Result
unsupportedOS'
stdSourcesListFor :: DebianSuite -> Property Debian
stdSourcesListFor :: DebianSuite -> Property Debian
stdSourcesListFor DebianSuite
suite = DebianSuite -> [SourcesGenerator] -> Property Debian
stdSourcesList' DebianSuite
suite []
stdSourcesList' :: DebianSuite -> [SourcesGenerator] -> Property Debian
stdSourcesList' :: DebianSuite -> [SourcesGenerator] -> Property Debian
stdSourcesList' DebianSuite
suite [SourcesGenerator]
more = Property DebianLike -> Property Debian
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property DebianLike -> Property Debian)
-> Property DebianLike -> Property Debian
forall a b. (a -> b) -> a -> b
$
String -> (String -> Property DebianLike) -> Property DebianLike
withMirror String
desc ((String -> Property DebianLike) -> Property DebianLike)
-> (String -> Property DebianLike) -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ \String
u -> [String] -> Property DebianLike
setSourcesList
((SourcesGenerator -> [String]) -> [SourcesGenerator] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\SourcesGenerator
gen -> SourcesGenerator
gen DebianSuite
suite) (String -> [SourcesGenerator]
generators String
u))
where
generators :: String -> [SourcesGenerator]
generators String
u = [String -> SourcesGenerator
binandsrc String
u, SourcesGenerator
securityUpdates] [SourcesGenerator] -> [SourcesGenerator] -> [SourcesGenerator]
forall a. [a] -> [a] -> [a]
++ [SourcesGenerator]
more
desc :: String
desc = (String
"standard sources.list for " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DebianSuite -> String
forall a. Show a => a -> String
show DebianSuite
suite)
type PinPriority = Int
suiteAvailablePinned
:: DebianSuite
-> PinPriority
-> RevertableProperty Debian Debian
suiteAvailablePinned :: DebianSuite -> Int -> RevertableProperty Debian Debian
suiteAvailablePinned DebianSuite
s Int
pin = Property Debian
available Property Debian
-> Property Debian -> RevertableProperty Debian Debian
forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> Property Debian
unavailable
where
available :: Property Debian
available :: Property Debian
available = Property Debian -> Property Debian
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property Debian -> Property Debian)
-> Property Debian -> Property Debian
forall a b. (a -> b) -> a -> b
$ String -> Props Debian -> Property Debian
forall k (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties (Bool -> String
desc Bool
True) (Props Debian -> Property Debian)
-> Props Debian -> Property Debian
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))
& String -> [String] -> Property UnixLike
File.hasContent String
prefFile (String -> DebianSuite -> Int -> [String]
suitePinBlock String
"*" DebianSuite
s Int
pin)
Props UnixLike
-> Property Debian
-> Props
(MetaTypes
(Combine
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
'[ '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
setSourcesFile
unavailable :: Property Debian
unavailable :: Property Debian
unavailable = Property DebianLike -> Property Debian
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property DebianLike -> Property Debian)
-> Property DebianLike -> Property Debian
forall a b. (a -> b) -> a -> b
$ String -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties (Bool -> String
desc Bool
False) (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))
& String -> Property UnixLike
File.notPresent String
sourcesFile
Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
update
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))
& String -> Property UnixLike
File.notPresent String
prefFile
setSourcesFile :: Property Debian
setSourcesFile :: Property Debian
setSourcesFile = Property DebianLike -> Property Debian
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property DebianLike -> Property Debian)
-> Property DebianLike -> Property Debian
forall a b. (a -> b) -> a -> b
$ String -> (String -> Property DebianLike) -> Property DebianLike
withMirror (Bool -> String
desc Bool
True) ((String -> Property DebianLike) -> Property DebianLike)
-> (String -> Property DebianLike) -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ \String
u ->
String
-> (OuterMetaTypesWitness
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Maybe System -> Propellor Result)
-> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes
-> Maybe System -> Propellor Result)
-> Property (MetaTypes metatypes)
withOS (Bool -> String
desc Bool
True) ((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
_ DebianSuite
hostSuite) Architecture
_))
| DebianSuite
s DebianSuite -> DebianSuite -> Bool
forall a. Eq a => a -> a -> Bool
/= DebianSuite
hostSuite -> 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
$
String -> [String] -> Property UnixLike
File.hasContent String
sourcesFile (String -> [String]
sources String
u)
Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
update
Maybe System
_ -> Propellor Result
noChange
sources :: String -> [String]
sources String
u = [String] -> [String]
dropBackports ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (SourcesGenerator -> [String]) -> [SourcesGenerator] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\SourcesGenerator
gen -> SourcesGenerator
gen DebianSuite
s) (String -> [SourcesGenerator]
generators String
u)
where
dropBackports :: [String] -> [String]
dropBackports
| String
"-backports" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` (DebianSuite -> String
showSuite DebianSuite
s) = [String] -> [String]
forall a. a -> a
id
| Bool
otherwise = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isInfixOf String
"-backports")
generators :: String -> [SourcesGenerator]
generators String
u = [String -> SourcesGenerator
binandsrc String
u, SourcesGenerator
securityUpdates]
prefFile :: String
prefFile = String
"/etc/apt/preferences.d/20" String -> ShowS
forall a. [a] -> [a] -> [a]
++ DebianSuite -> String
showSuite DebianSuite
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".pref"
sourcesFile :: String
sourcesFile = String
"/etc/apt/sources.list.d/" String -> ShowS
forall a. [a] -> [a] -> [a]
++ DebianSuite -> String
showSuite DebianSuite
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".list"
desc :: Bool -> String
desc Bool
True = String
"Debian " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DebianSuite -> String
showSuite DebianSuite
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" pinned, priority " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
pin
desc Bool
False = String
"Debian " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DebianSuite -> String
showSuite DebianSuite
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" not pinned"
setSourcesList :: [Line] -> Property DebianLike
setSourcesList :: [String] -> Property DebianLike
setSourcesList [String]
ls = String
sourcesList String -> [String] -> Property UnixLike
`File.hasContent` [String]
ls Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
update
setSourcesListD :: [Line] -> FilePath -> Property DebianLike
setSourcesListD :: [String] -> String -> Property DebianLike
setSourcesListD [String]
ls String
basename = String
f String -> [String] -> Property UnixLike
`File.hasContent` [String]
ls Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
update
where
f :: String
f = String
"/etc/apt/sources.list.d/" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
basename String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".list"
runApt :: [String] -> UncheckedProperty DebianLike
runApt :: [String] -> UncheckedProperty DebianLike
runApt [String]
ps = UncheckedProperty UnixLike -> UncheckedProperty DebianLike
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (UncheckedProperty UnixLike -> UncheckedProperty DebianLike)
-> UncheckedProperty UnixLike -> UncheckedProperty DebianLike
forall a b. (a -> b) -> a -> b
$ String
-> [String] -> [(String, String)] -> UncheckedProperty UnixLike
cmdPropertyEnv String
"apt-get" [String]
ps [(String, String)]
noninteractiveEnv
noninteractiveEnv :: [(String, String)]
noninteractiveEnv :: [(String, String)]
noninteractiveEnv =
[ (String
"DEBIAN_FRONTEND", String
"noninteractive")
, (String
"APT_LISTCHANGES_FRONTEND", String
"none")
]
update :: Property DebianLike
update :: Property DebianLike
update = String -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties String
desc (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))
& Property DebianLike
pendingConfigured
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
aptupdate
where
desc :: String
desc = String
"apt update"
aptupdate :: Property DebianLike
aptupdate :: Property DebianLike
aptupdate = String
-> (OuterMetaTypesWitness
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Maybe System -> Propellor Result)
-> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes
-> Maybe System -> Propellor Result)
-> Property (MetaTypes metatypes)
withOS String
desc ((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
_ DebianSuite
suite) Architecture
_))
| Bool -> Bool
not (DebianSuite -> Bool
isStable DebianSuite
suite) -> 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
$
[String] -> UncheckedProperty DebianLike
runApt [String
"update", String
"--allow-releaseinfo-change"]
UncheckedProperty DebianLike -> Result -> Property DebianLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
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
$
[String] -> UncheckedProperty DebianLike
runApt [String
"update"]
UncheckedProperty DebianLike -> Result -> Property DebianLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
upgrade :: Property DebianLike
upgrade :: Property DebianLike
upgrade = String -> Property DebianLike
upgrade' String
"dist-upgrade"
upgrade' :: String -> Property DebianLike
upgrade' :: String -> Property DebianLike
upgrade' String
p = String -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties (String
"apt " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
p) (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))
& Property DebianLike
pendingConfigured
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))
& [String] -> UncheckedProperty DebianLike
runApt [String
"-y", String
p]
UncheckedProperty DebianLike -> Result -> Property DebianLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
safeUpgrade :: Property DebianLike
safeUpgrade :: Property DebianLike
safeUpgrade = String -> Property DebianLike
upgrade' String
"upgrade"
pendingConfigured :: Property DebianLike
pendingConfigured :: Property DebianLike
pendingConfigured = 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
$
String
-> [String] -> [(String, String)] -> UncheckedProperty UnixLike
cmdPropertyEnv String
"dpkg" [String
"--configure", String
"--pending"] [(String, String)]
noninteractiveEnv
UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
Property UnixLike -> String -> Property UnixLike
forall p. IsProp p => p -> String -> p
`describe` String
"dpkg configured pending"
type Package = String
installed :: [Package] -> Property DebianLike
installed :: [String] -> Property DebianLike
installed = [String] -> [String] -> Property DebianLike
installed' [String
"-y"]
installedMin :: [Package] -> Property DebianLike
installedMin :: [String] -> Property DebianLike
installedMin = [String] -> [String] -> Property DebianLike
installed' [String
"--no-install-recommends", String
"-y"]
installed' :: [String] -> [Package] -> Property DebianLike
installed' :: [String] -> [String] -> Property DebianLike
installed' [String]
params [String]
ps = Property DebianLike -> Property DebianLike
robustly (Property DebianLike -> Property DebianLike)
-> Property DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ IO Bool -> UncheckedProperty DebianLike -> Property DebianLike
forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Bool -> Bool
not (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String] -> IO Bool
isInstalled' [String]
ps) UncheckedProperty DebianLike
go
Property DebianLike -> String -> Property DebianLike
forall p. IsProp p => p -> String -> p
`describe` [String] -> String
unwords (String
"apt installed"String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ps)
where
go :: UncheckedProperty DebianLike
go = [String] -> UncheckedProperty DebianLike
runApt ([String]
params [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"install"] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
ps)
backportInstalled :: [Package] -> Property Debian
backportInstalled :: [String] -> Property Debian
backportInstalled = [String] -> [String] -> Property Debian
backportInstalled' [String
"-y"]
backportInstalledMin :: [Package] -> Property Debian
backportInstalledMin :: [String] -> Property Debian
backportInstalledMin = [String] -> [String] -> Property Debian
backportInstalled' [String
"--no-install-recommends", String
"-y"]
backportInstalled' :: [String] -> [Package] -> Property Debian
backportInstalled' :: [String] -> [String] -> Property Debian
backportInstalled' [String]
params [String]
ps = String
-> (OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
-> Maybe System -> Propellor Result)
-> Property Debian
forall k (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes
-> Maybe System -> Propellor Result)
-> Property (MetaTypes metatypes)
withOS String
desc ((OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
-> Maybe System -> Propellor Result)
-> Property Debian)
-> (OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
-> Maybe System -> Propellor Result)
-> Property Debian
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
w Maybe System
o -> case Maybe System
o of
(Just (System (Debian DebianKernel
_ DebianSuite
suite) Architecture
_)) -> case DebianSuite -> Maybe String
backportSuite DebianSuite
suite of
Maybe String
Nothing -> Propellor Result
HasCallStack => Propellor Result
unsupportedOS'
Just String
bs -> OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
-> Property DebianLike -> Propellor Result
forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness '[ 'Targeting 'OSDebian]
w (Property DebianLike -> Propellor Result)
-> Property DebianLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$
[String] -> UncheckedProperty DebianLike
runApt ((String
"install"String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
params) [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ((String -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'/'Char -> ShowS
forall a. a -> [a] -> [a]
:String
bs) ShowS -> [String] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String]
ps))
UncheckedProperty DebianLike -> String -> Property DebianLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> String -> Property i
`changesFile` String
dpkgStatus
Maybe System
_ -> Propellor Result
HasCallStack => Propellor Result
unsupportedOS'
where
desc :: String
desc = [String] -> String
unwords (String
"apt installed backport"String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ps)
removed :: [Package] -> Property DebianLike
removed :: [String] -> Property DebianLike
removed [String]
ps = IO Bool -> UncheckedProperty DebianLike -> Property DebianLike
forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check ((InstallStatus -> Bool) -> [InstallStatus] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (InstallStatus -> InstallStatus -> Bool
forall a. Eq a => a -> a -> Bool
== InstallStatus
IsInstalled) ([InstallStatus] -> Bool) -> IO [InstallStatus] -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String] -> IO [InstallStatus]
getInstallStatus [String]
ps)
([String] -> UncheckedProperty DebianLike
runApt ([String
"-y", String
"remove"] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
ps))
Property DebianLike -> String -> Property DebianLike
forall p. IsProp p => p -> String -> p
`describe` [String] -> String
unwords (String
"apt removed"String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ps)
buildDep :: [Package] -> Property DebianLike
buildDep :: [String] -> Property DebianLike
buildDep [String]
ps = Property DebianLike -> Property DebianLike
robustly (Property DebianLike -> Property DebianLike)
-> Property DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ UncheckedProperty DebianLike
go
UncheckedProperty DebianLike -> String -> Property DebianLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> String -> Property i
`changesFile` String
dpkgStatus
Property DebianLike -> String -> Property DebianLike
forall p. IsProp p => p -> String -> p
`describe` [String] -> String
unwords (String
"apt build-dep"String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ps)
where
go :: UncheckedProperty DebianLike
go = [String] -> UncheckedProperty DebianLike
runApt ([String] -> UncheckedProperty DebianLike)
-> [String] -> UncheckedProperty DebianLike
forall a b. (a -> b) -> a -> b
$ [String
"-y", String
"build-dep"] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
ps
buildDepIn :: FilePath -> Property DebianLike
buildDepIn :: String -> Property DebianLike
buildDepIn String
dir = UncheckedProperty DebianLike
go
UncheckedProperty DebianLike -> String -> Property DebianLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> String -> Property i
`changesFile` String
dpkgStatus
Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [String] -> Property DebianLike
installedMin [String
"devscripts", String
"equivs"]
where
go :: UncheckedProperty DebianLike
go :: UncheckedProperty DebianLike
go = Property DebianLike -> UncheckedProperty DebianLike
forall i. Property i -> UncheckedProperty i
unchecked (Property DebianLike -> UncheckedProperty DebianLike)
-> Property DebianLike -> UncheckedProperty DebianLike
forall a b. (a -> b) -> a -> b
$ String -> Propellor Result -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String -> Propellor Result -> Property (MetaTypes metatypes)
property (String
"build-dep in " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
dir) (Propellor Result -> Property DebianLike)
-> Propellor Result -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ IO Result -> Propellor Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> Propellor Result) -> IO Result -> Propellor Result
forall a b. (a -> b) -> a -> b
$
String -> (String -> IO Result) -> IO Result
forall (m :: * -> *) a.
(MonadMask m, MonadIO m) =>
String -> (String -> m a) -> m a
withTmpDir String
"build-dep" ((String -> IO Result) -> IO Result)
-> (String -> IO Result) -> IO Result
forall a b. (a -> b) -> a -> b
$ \String
tmpdir -> do
Bool -> Result
cmdResult (Bool -> Result) -> IO Bool -> IO Result
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
-> [CommandParam] -> (CreateProcess -> CreateProcess) -> IO Bool
boolSystem' String
"mk-build-deps"
[ String -> CommandParam
File (String -> CommandParam) -> String -> CommandParam
forall a b. (a -> b) -> a -> b
$ String
dir String -> ShowS
</> String
"debian" String -> ShowS
</> String
"control"
, String -> CommandParam
Param String
"--install"
, String -> CommandParam
Param String
"--tool"
, String -> CommandParam
Param String
"apt-get -y --no-install-recommends"
] (\CreateProcess
p -> CreateProcess
p { cwd :: Maybe String
cwd = String -> Maybe String
forall a. a -> Maybe a
Just String
tmpdir })
type AptPackagePref = String
pinnedTo
:: [AptPackagePref]
-> [(DebianSuite, PinPriority)]
-> RevertableProperty Debian Debian
pinnedTo :: [String]
-> [(DebianSuite, Int)] -> RevertableProperty Debian Debian
pinnedTo [String]
ps [(DebianSuite, Int)]
pins = [RevertableProperty Debian Debian]
-> RevertableProperty Debian Debian
forall a. Monoid a => [a] -> a
mconcat ((String -> RevertableProperty Debian Debian)
-> [String] -> [RevertableProperty Debian Debian]
forall a b. (a -> b) -> [a] -> [b]
map (\String
p -> String -> [(DebianSuite, Int)] -> RevertableProperty Debian Debian
pinnedTo' String
p [(DebianSuite, Int)]
pins) [String]
ps)
RevertableProperty Debian Debian
-> String -> RevertableProperty Debian Debian
forall p. IsProp p => p -> String -> p
`describe` [String] -> String
unwords ((String
"pinned to " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
showSuites)String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ps)
where
showSuites :: String
showSuites = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ DebianSuite -> String
showSuite (DebianSuite -> String)
-> ((DebianSuite, Int) -> DebianSuite)
-> (DebianSuite, Int)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DebianSuite, Int) -> DebianSuite
forall a b. (a, b) -> a
fst ((DebianSuite, Int) -> String) -> [(DebianSuite, Int)] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(DebianSuite, Int)]
pins
pinnedTo'
:: AptPackagePref
-> [(DebianSuite, PinPriority)]
-> RevertableProperty Debian Debian
pinnedTo' :: String -> [(DebianSuite, Int)] -> RevertableProperty Debian Debian
pinnedTo' String
p [(DebianSuite, Int)]
pins =
(Property UnixLike -> Property Debian
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property UnixLike -> Property Debian)
-> Property UnixLike -> Property Debian
forall a b. (a -> b) -> a -> b
$ String
prefFile String -> [String] -> Property UnixLike
`File.hasContent` [String]
prefs)
Property Debian
-> Property Debian -> RevertableProperty Debian Debian
forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> (Property UnixLike -> Property Debian
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property UnixLike -> Property Debian)
-> Property UnixLike -> Property Debian
forall a b. (a -> b) -> a -> b
$ String -> Property UnixLike
File.notPresent String
prefFile)
where
prefs :: [String]
prefs = ((DebianSuite, Int) -> [String] -> [String])
-> [String] -> [(DebianSuite, Int)] -> [String]
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (DebianSuite, Int) -> [String] -> [String]
step [] [(DebianSuite, Int)]
pins
step :: (DebianSuite, Int) -> [String] -> [String]
step (DebianSuite
suite, Int
pin) [String]
ls = [String]
ls [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> DebianSuite -> Int -> [String]
suitePinBlock String
p DebianSuite
suite Int
pin [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
""]
prefFile :: String
prefFile = String
"/etc/apt/preferences.d/10propellor_"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
File.configFileName String
p String -> ShowS
<.> String
"pref"
robustly :: Property DebianLike -> Property DebianLike
robustly :: Property DebianLike -> Property DebianLike
robustly Property DebianLike
p = Property DebianLike
p Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`fallback` (Property DebianLike
update Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Property DebianLike
p)
isInstalled :: Package -> IO Bool
isInstalled :: String -> IO Bool
isInstalled String
p = [String] -> IO Bool
isInstalled' [String
p]
isInstalled' :: [Package] -> IO Bool
isInstalled' :: [String] -> IO Bool
isInstalled' [String]
ps = do
[InstallStatus]
is <- [String] -> IO [InstallStatus]
getInstallStatus [String]
ps
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ (InstallStatus -> Bool) -> [InstallStatus] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (InstallStatus -> InstallStatus -> Bool
forall a. Eq a => a -> a -> Bool
== InstallStatus
IsInstalled) [InstallStatus]
is Bool -> Bool -> Bool
&& [InstallStatus] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [InstallStatus]
is Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
ps
data InstallStatus = IsInstalled | NotInstalled
deriving (Int -> InstallStatus -> ShowS
[InstallStatus] -> ShowS
InstallStatus -> String
(Int -> InstallStatus -> ShowS)
-> (InstallStatus -> String)
-> ([InstallStatus] -> ShowS)
-> Show InstallStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InstallStatus] -> ShowS
$cshowList :: [InstallStatus] -> ShowS
show :: InstallStatus -> String
$cshow :: InstallStatus -> String
showsPrec :: Int -> InstallStatus -> ShowS
$cshowsPrec :: Int -> InstallStatus -> ShowS
Show, InstallStatus -> InstallStatus -> Bool
(InstallStatus -> InstallStatus -> Bool)
-> (InstallStatus -> InstallStatus -> Bool) -> Eq InstallStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstallStatus -> InstallStatus -> Bool
$c/= :: InstallStatus -> InstallStatus -> Bool
== :: InstallStatus -> InstallStatus -> Bool
$c== :: InstallStatus -> InstallStatus -> Bool
Eq)
getInstallStatus :: [Package] -> IO [InstallStatus]
getInstallStatus :: [String] -> IO [InstallStatus]
getInstallStatus [String]
ps = (String -> Maybe InstallStatus) -> [String] -> [InstallStatus]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe String -> Maybe InstallStatus
parse ([String] -> [InstallStatus])
-> (String -> [String]) -> String -> [InstallStatus]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines (String -> [InstallStatus]) -> IO String -> IO [InstallStatus]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO String
policy
where
parse :: String -> Maybe InstallStatus
parse String
l
| String
"Installed: (none)" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
l = InstallStatus -> Maybe InstallStatus
forall a. a -> Maybe a
Just InstallStatus
NotInstalled
| String
"Installed: " String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isInfixOf` String
l = InstallStatus -> Maybe InstallStatus
forall a. a -> Maybe a
Just InstallStatus
IsInstalled
| Bool
otherwise = Maybe InstallStatus
forall a. Maybe a
Nothing
policy :: IO String
policy = do
[(String, String)]
environ <- String -> String -> [(String, String)] -> [(String, String)]
forall k v. Eq k => k -> v -> [(k, v)] -> [(k, v)]
addEntry String
"LANG" String
"C" ([(String, String)] -> [(String, String)])
-> IO [(String, String)] -> IO [(String, String)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [(String, String)]
getEnvironment
String -> [String] -> Maybe [(String, String)] -> IO String
readProcessEnv String
"apt-cache" (String
"policy"String -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
ps) ([(String, String)] -> Maybe [(String, String)]
forall a. a -> Maybe a
Just [(String, String)]
environ)
autoRemove :: Property DebianLike
autoRemove :: Property DebianLike
autoRemove = [String] -> UncheckedProperty DebianLike
runApt [String
"-y", String
"autoremove"]
UncheckedProperty DebianLike -> String -> Property DebianLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> String -> Property i
`changesFile` String
dpkgStatus
Property DebianLike -> String -> Property DebianLike
forall p. IsProp p => p -> String -> p
`describe` String
"apt autoremove"
unattendedUpgrades :: RevertableProperty DebianLike DebianLike
unattendedUpgrades :: RevertableProperty DebianLike DebianLike
unattendedUpgrades = Property DebianLike
enable Property DebianLike
-> Property DebianLike -> RevertableProperty DebianLike DebianLike
forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> Property DebianLike
disable
where
enable :: CombinedType (Property DebianLike) (Property UnixLike)
enable = Bool -> Property DebianLike
setup Bool
True
Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` String -> Property DebianLike
Service.running String
"cron"
Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Property DebianLike
configure
Property DebianLike
-> Property UnixLike
-> CombinedType (Property DebianLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` String -> Property UnixLike
File.notPresent String
"/etc/apt/apt.conf.d/50unattended-upgrades.ucf-dist"
disable :: Property DebianLike
disable = Bool -> Property DebianLike
setup Bool
False
setup :: Bool -> Property DebianLike
setup Bool
enabled = (if Bool
enabled then [String] -> Property DebianLike
installed else [String] -> Property DebianLike
removed) [String
"unattended-upgrades"]
Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` String -> [(String, String, String)] -> Property DebianLike
reConfigure String
"unattended-upgrades"
[(String
"unattended-upgrades/enable_auto_updates" , String
"boolean", String
v)]
Property DebianLike -> String -> Property DebianLike
forall p. IsProp p => p -> String -> p
`describe` (String
"unattended upgrades " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
v)
where
v :: String
v
| Bool
enabled = String
"true"
| Bool
otherwise = String
"false"
configure :: Property DebianLike
configure :: Property DebianLike
configure = String -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList String
"unattended upgrades configured" (Props DebianLike -> Property DebianLike)
-> Props DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
Props UnixLike
-> Property DebianLike
-> Props
(MetaTypes
(Combine
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property DebianLike
enableupgrading
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))
& String
unattendedconfig String -> String -> Property UnixLike
`File.containsLine` String
"Unattended-Upgrade::Mail \"root\";"
where
enableupgrading :: Property DebianLike
enableupgrading :: Property DebianLike
enableupgrading = String
-> (OuterMetaTypesWitness
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Maybe System -> Propellor Result)
-> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String
-> (OuterMetaTypesWitness metatypes
-> Maybe System -> Propellor Result)
-> Property (MetaTypes metatypes)
withOS String
"unattended upgrades configured" ((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
_ DebianSuite
suite) Architecture
_))
| Bool -> Bool
not (DebianSuite -> Bool
isStable DebianSuite
suite) -> OuterMetaTypesWitness
'[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish]
-> Property UnixLike -> 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 UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$
String
unattendedconfig
String -> String -> Property UnixLike
`File.containsLine`
(String
"Unattended-Upgrade::Origins-Pattern { \"o=Debian,a="String -> ShowS
forall a. [a] -> [a] -> [a]
++DebianSuite -> String
showSuite DebianSuite
suiteString -> ShowS
forall a. [a] -> [a] -> [a]
++String
"\"; };")
Maybe System
_ -> Propellor Result
noChange
unattendedconfig :: String
unattendedconfig = String
"/etc/apt/apt.conf.d/50unattended-upgrades"
periodicUpdates :: Property DebianLike
periodicUpdates :: Property DebianLike
periodicUpdates = 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
$ String
"/etc/apt/apt.conf.d/02periodic" String -> [String] -> Property UnixLike
`File.hasContent`
[ String
"APT::Periodic::Enable \"1\";"
, String
"APT::Periodic::Update-Package-Lists \"1\";"
, String
"APT::Periodic::Download-Upgradeable-Packages \"1\";"
, String
"APT::Periodic::Verbose \"1\";"
]
type DebconfTemplate = String
type DebconfTemplateType = String
type DebconfTemplateValue = String
reConfigure :: Package -> [(DebconfTemplate, DebconfTemplateType, DebconfTemplateValue)] -> Property DebianLike
reConfigure :: String -> [(String, String, String)] -> Property DebianLike
reConfigure String
package [(String, String, String)]
vals = Property DebianLike -> Property DebianLike
forall (p :: * -> *) (untightened :: [MetaType])
(tightened :: [MetaType]).
(TightenTargets p, TightenTargetsAllowed untightened tightened,
SingI tightened) =>
p (MetaTypes untightened) -> p (MetaTypes tightened)
tightenTargets (Property DebianLike -> Property DebianLike)
-> Property DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$
Property UnixLike
reconfigure
Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` Property DebianLike
setselections
Property DebianLike -> String -> Property DebianLike
forall p. IsProp p => p -> String -> p
`describe` (String
"reconfigure " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
package)
where
setselections :: Property DebianLike
setselections :: Property DebianLike
setselections = String -> Propellor Result -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String -> Propellor Result -> Property (MetaTypes metatypes)
property String
"preseed" (Propellor Result -> Property DebianLike)
-> Propellor Result -> Property DebianLike
forall a b. (a -> b) -> a -> b
$
if [(String, String, String)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(String, String, String)]
vals
then Propellor Result
noChange
else IO () -> Propellor Result
makeChange (IO () -> Propellor Result) -> IO () -> Propellor Result
forall a b. (a -> b) -> a -> b
$
StdHandle
-> CreateProcessRunner
-> CreateProcess
-> (Handle -> IO ())
-> IO ()
forall a.
StdHandle
-> CreateProcessRunner -> CreateProcess -> (Handle -> IO a) -> IO a
withHandle StdHandle
StdinHandle CreateProcessRunner
createProcessSuccess
(String -> [String] -> CreateProcess
proc String
"debconf-set-selections" []) ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
[(String, String, String)]
-> ((String, String, String) -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(String, String, String)]
vals (((String, String, String) -> IO ()) -> IO ())
-> ((String, String, String) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(String
tmpl, String
tmpltype, String
value) ->
Handle -> String -> IO ()
hPutStrLn Handle
h (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unwords [String
package, String
tmpl, String
tmpltype, String
value]
Handle -> IO ()
hClose Handle
h
reconfigure :: Property UnixLike
reconfigure = String
-> [String] -> [(String, String)] -> UncheckedProperty UnixLike
cmdPropertyEnv String
"dpkg-reconfigure" [String
"-fnone", String
package] [(String, String)]
noninteractiveEnv
UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
serviceInstalledRunning :: Package -> Property DebianLike
serviceInstalledRunning :: String -> Property DebianLike
serviceInstalledRunning String
svc = String -> Property DebianLike
Service.running String
svc Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [String] -> Property DebianLike
installed [String
svc]
data AptKey = AptKey
{ AptKey -> String
keyname :: String
, AptKey -> String
pubkey :: String
}
trustsKey :: AptKey -> RevertableProperty DebianLike DebianLike
trustsKey :: AptKey -> RevertableProperty DebianLike DebianLike
trustsKey AptKey
k = AptKey -> Property DebianLike
trustsKey' AptKey
k Property DebianLike
-> Property DebianLike -> RevertableProperty DebianLike DebianLike
forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> AptKey -> Property DebianLike
untrustKey AptKey
k
trustsKey' :: AptKey -> Property DebianLike
trustsKey' :: AptKey -> Property DebianLike
trustsKey' AptKey
k = IO Bool -> Property DebianLike -> Property DebianLike
forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (Bool -> Bool
not (Bool -> Bool) -> IO Bool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Bool
doesFileExist String
f) (Property DebianLike -> Property DebianLike)
-> Property DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ String -> Propellor Result -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
String -> Propellor Result -> Property (MetaTypes metatypes)
property String
desc (Propellor Result -> Property DebianLike)
-> Propellor Result -> Property DebianLike
forall a b. (a -> b) -> a -> b
$ IO () -> Propellor Result
makeChange (IO () -> Propellor Result) -> IO () -> Propellor Result
forall a b. (a -> b) -> a -> b
$ do
StdHandle
-> CreateProcessRunner
-> CreateProcess
-> (Handle -> IO ())
-> IO ()
forall a.
StdHandle
-> CreateProcessRunner -> CreateProcess -> (Handle -> IO a) -> IO a
withHandle StdHandle
StdinHandle CreateProcessRunner
createProcessSuccess
(String -> [String] -> CreateProcess
proc String
"apt-key" [String
"--keyring", String
f, String
"add", String
"-"]) ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
Handle -> String -> IO ()
hPutStr Handle
h (AptKey -> String
pubkey AptKey
k)
Handle -> IO ()
hClose Handle
h
String -> IO ()
nukeFile (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
f String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"~"
where
desc :: String
desc = String
"apt trusts key " String -> ShowS
forall a. [a] -> [a] -> [a]
++ AptKey -> String
keyname AptKey
k
f :: String
f = AptKey -> String
aptKeyFile AptKey
k
untrustKey :: AptKey -> Property DebianLike
untrustKey :: AptKey -> Property DebianLike
untrustKey = 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)
-> (AptKey -> Property UnixLike) -> AptKey -> Property DebianLike
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Property UnixLike
File.notPresent (String -> Property UnixLike)
-> (AptKey -> String) -> AptKey -> Property UnixLike
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AptKey -> String
aptKeyFile
aptKeyFile :: AptKey -> FilePath
aptKeyFile :: AptKey -> String
aptKeyFile AptKey
k = String
"/etc/apt/trusted.gpg.d" String -> ShowS
</> AptKey -> String
keyname AptKey
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
".gpg"
cacheCleaned :: Property DebianLike
cacheCleaned :: Property DebianLike
cacheCleaned = 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
$ String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"apt-get" [String
"clean"]
UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
NoChange
Property UnixLike -> String -> Property UnixLike
forall p. IsProp p => p -> String -> p
`describe` String
"apt cache cleaned"
hasForeignArch :: String -> Property DebianLike
hasForeignArch :: String -> Property DebianLike
hasForeignArch String
arch = IO Bool -> Property DebianLike -> Property DebianLike
forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check IO Bool
notAdded (Property UnixLike
add Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Property DebianLike
update)
Property DebianLike -> String -> Property DebianLike
forall p. IsProp p => p -> String -> p
`describe` (String
"dpkg has foreign architecture " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
arch)
where
notAdded :: IO Bool
notAdded = (String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
notElem String
arch ([String] -> Bool) -> (String -> [String]) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines) (String -> Bool) -> IO String -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> [String] -> IO String
readProcess String
"dpkg" [String
"--print-foreign-architectures"]
add :: Property UnixLike
add = String -> [String] -> UncheckedProperty UnixLike
cmdProperty String
"dpkg" [String
"--add-architecture", String
arch]
UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange
noPDiffs :: Property DebianLike
noPDiffs :: Property DebianLike
noPDiffs = 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
$ String
"/etc/apt/apt.conf.d/20pdiffs" String -> [String] -> Property UnixLike
`File.hasContent`
[ String
"Acquire::PDiffs \"false\";" ]
suitePin :: DebianSuite -> String
suitePin :: DebianSuite -> String
suitePin DebianSuite
s = DebianSuite -> String
prefix DebianSuite
s String -> ShowS
forall a. [a] -> [a] -> [a]
++ DebianSuite -> String
showSuite DebianSuite
s
where
prefix :: DebianSuite -> String
prefix (Stable String
_) = String
"n="
prefix DebianSuite
_ = String
"a="
suitePinBlock :: AptPackagePref -> DebianSuite -> PinPriority -> [Line]
suitePinBlock :: String -> DebianSuite -> Int -> [String]
suitePinBlock String
p DebianSuite
suite Int
pin =
[ String
"Explanation: This file added by propellor"
, String
"Package: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
p
, String
"Pin: release " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DebianSuite -> String
suitePin DebianSuite
suite
, String
"Pin-Priority: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall t. ConfigurableValue t => t -> String
val Int
pin
]
dpkgStatus :: FilePath
dpkgStatus :: String
dpkgStatus = String
"/var/lib/dpkg/status"
proxy :: Url -> Property (HasInfo + DebianLike)
proxy :: String -> Property (HasInfo + DebianLike)
proxy String
u = Property DebianLike
-> Info
-> Property
(MetaTypes
'[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes' :: k) metatypes.
(MetaTypes metatypes' ~ (HasInfo + metatypes), SingI metatypes') =>
Property metatypes -> Info -> Property (MetaTypes metatypes')
setInfoProperty (String -> Property DebianLike
proxy' String
u) (String -> Info
proxyInfo String
u)
where
proxyInfo :: String -> Info
proxyInfo = InfoVal HostAptProxy -> Info
forall v. IsInfo v => v -> Info
toInfo (InfoVal HostAptProxy -> Info)
-> (String -> InfoVal HostAptProxy) -> String -> Info
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HostAptProxy -> InfoVal HostAptProxy
forall v. v -> InfoVal v
InfoVal (HostAptProxy -> InfoVal HostAptProxy)
-> (String -> HostAptProxy) -> String -> InfoVal HostAptProxy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> HostAptProxy
HostAptProxy
proxy' :: Url -> Property DebianLike
proxy' :: String -> Property DebianLike
proxy' String
u = 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
$
String
"/etc/apt/apt.conf.d/20proxy" String -> [String] -> Property UnixLike
`File.hasContent`
[ String
"Acquire::HTTP::Proxy \"" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
u String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\";" ]
Property UnixLike -> String -> Property UnixLike
forall p. IsProp p => p -> String -> p
`describe` String
desc
where
desc :: String
desc = (String
u String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" apt proxy selected")
useLocalCacher :: Property (HasInfo + DebianLike)
useLocalCacher :: Property (HasInfo + DebianLike)
useLocalCacher = String -> Property (HasInfo + DebianLike)
proxy String
"http://localhost:3142"
Property
(MetaTypes
'[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> CombinedType
(Property
(MetaTypes
'[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
(Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` String -> Property DebianLike
serviceInstalledRunning String
"apt-cacher-ng"
Property
(MetaTypes
'[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> String
-> Property
(MetaTypes
'[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall p. IsProp p => p -> String -> p
`describe` String
"apt uses local apt cacher"