{-# LANGUAGE DeriveDataTypeable, TypeFamilies #-}

module Propellor.Property.Ssh (
	installed,
	restarted,
	PubKeyText,
	SshKeyType(..),
	-- * Daemon configuration
	sshdConfig,
	ConfigKeyword,
	setSshdConfigBool,
	setSshdConfig,
	RootLogin(..),
	permitRootLogin,
	passwordAuthentication,
	noPasswords,
	listenPort,
	-- * Host keys
	randomHostKeys,
	hostKeys,
	hostKey,
	hostPubKey,
	getHostPubKey,
	-- * User keys and configuration
	userKeys,
	userKeyAt,
	knownHost,
	unknownHost,
	authorizedKeysFrom,
	unauthorizedKeysFrom,
	authorizedKeys,
	authorizedKey,
	hasAuthorizedKeys,
	getUserPubKeys,
) where

import Propellor.Base
import qualified Propellor.Property.File as File
import qualified Propellor.Property.Service as Service
import qualified Propellor.Property.Apt as Apt
import Propellor.Property.User
import Propellor.Types.Info

import System.PosixCompat
import qualified Data.Map as M
import qualified Data.Set as S
import qualified Data.Semigroup as Sem
import Data.List

installed :: Property UnixLike
installed :: Property UnixLike
installed = [Char]
"ssh installed" [Char] -> Property UnixLike -> Property UnixLike
forall i. IsProp (Property i) => [Char] -> Property i -> Property i
==> (Property DebianLike
aptinstall Property DebianLike -> Property UnixLike -> Property UnixLike
forall k ka kb (c :: k) (a :: ka) (b :: kb).
(HasCallStack, SingKind 'KProxy, SingKind 'KProxy,
 DemoteRep 'KProxy ~ [MetaType], DemoteRep 'KProxy ~ [MetaType],
 SingI c) =>
Property (MetaTypes a)
-> Property (MetaTypes b) -> Property (MetaTypes c)
`pickOS` Property UnixLike
unsupportedOS)
  where
	aptinstall :: Property DebianLike
	aptinstall :: Property DebianLike
aptinstall = [[Char]] -> Property DebianLike
Apt.installed [[Char]
"ssh"]

restarted :: Property DebianLike
restarted :: Property DebianLike
restarted = [Char] -> Property DebianLike
Service.restarted [Char]
"ssh"

sshBool :: Bool -> String
sshBool :: Bool -> [Char]
sshBool Bool
True = [Char]
"yes"
sshBool Bool
False = [Char]
"no"

sshdConfig :: FilePath
sshdConfig :: [Char]
sshdConfig = [Char]
"/etc/ssh/sshd_config"

type ConfigKeyword = String

setSshdConfigBool :: ConfigKeyword -> Bool -> Property DebianLike
setSshdConfigBool :: [Char] -> Bool -> Property DebianLike
setSshdConfigBool [Char]
setting Bool
allowed = [Char] -> [Char] -> Property DebianLike
setSshdConfig [Char]
setting (Bool -> [Char]
sshBool Bool
allowed)

setSshdConfig :: ConfigKeyword -> String -> Property DebianLike
setSshdConfig :: [Char] -> [Char] -> Property DebianLike
setSshdConfig [Char]
setting [Char]
v = [Char] -> ([[Char]] -> [[Char]]) -> [Char] -> Property UnixLike
forall c.
(FileContent c, Eq c) =>
[Char] -> (c -> c) -> [Char] -> Property UnixLike
File.fileProperty [Char]
desc [[Char]] -> [[Char]]
f [Char]
sshdConfig
	Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
restarted
  where
	desc :: [Char]
desc = [[Char]] -> [Char]
unwords [ [Char]
"ssh config:", [Char]
setting, [Char]
v ]
	cfgline :: [Char]
cfgline = [Char]
setting [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
v
	wantedline :: [Char] -> Bool
wantedline [Char]
s
		| [Char]
s [Char] -> [Char] -> Bool
forall a. Eq a => a -> a -> Bool
== [Char]
cfgline = Bool
True
		| ([Char]
setting [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" ") [Char] -> [Char] -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` [Char]
s = Bool
False
		| Bool
otherwise = Bool
True
	f :: [[Char]] -> [[Char]]
f [[Char]]
ls
		| [Char]
cfgline [Char] -> [[Char]] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [[Char]]
ls = ([Char] -> Bool) -> [[Char]] -> [[Char]]
forall a. (a -> Bool) -> [a] -> [a]
filter [Char] -> Bool
wantedline [[Char]]
ls
		| Bool
otherwise = ([Char] -> Bool) -> [[Char]] -> [[Char]]
forall a. (a -> Bool) -> [a] -> [a]
filter [Char] -> Bool
wantedline [[Char]]
ls [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]
cfgline]

data RootLogin
	= RootLogin Bool  -- ^ allow or prevent root login
	| WithoutPassword -- ^ disable password authentication for root, while allowing other authentication methods
	| ForcedCommandsOnly -- ^ allow root login with public-key authentication, but only if a forced command has been specified for the public key

permitRootLogin :: RootLogin -> Property DebianLike
permitRootLogin :: RootLogin -> Property DebianLike
permitRootLogin (RootLogin Bool
b) = [Char] -> Bool -> Property DebianLike
setSshdConfigBool [Char]
"PermitRootLogin" Bool
b
permitRootLogin RootLogin
WithoutPassword = [Char] -> [Char] -> Property DebianLike
setSshdConfig [Char]
"PermitRootLogin" [Char]
"without-password"
permitRootLogin RootLogin
ForcedCommandsOnly = [Char] -> [Char] -> Property DebianLike
setSshdConfig [Char]
"PermitRootLogin" [Char]
"forced-commands-only"

passwordAuthentication :: Bool -> Property DebianLike
passwordAuthentication :: Bool -> Property DebianLike
passwordAuthentication = [Char] -> Bool -> Property DebianLike
setSshdConfigBool [Char]
"PasswordAuthentication"

-- | Configure ssh to not allow password logins.
--
-- To prevent lock-out, this is done only once root's
-- authorized_keys is in place.
noPasswords :: Property DebianLike
noPasswords :: Property DebianLike
noPasswords = IO Bool -> Property DebianLike -> Property DebianLike
forall (p :: * -> *) i (m :: * -> *).
(Checkable p i, LiftPropellor m) =>
m Bool -> p i -> Property i
check (User -> IO Bool
hasAuthorizedKeys ([Char] -> User
User [Char]
"root")) (Property DebianLike -> Property DebianLike)
-> Property DebianLike -> Property DebianLike
forall a b. (a -> b) -> a -> b
$
	Bool -> Property DebianLike
passwordAuthentication Bool
False

dotDir :: User -> IO FilePath
dotDir :: User -> IO [Char]
dotDir User
user = do
	[Char]
h <- User -> IO [Char]
homedir User
user
	[Char] -> IO [Char]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Char] -> IO [Char]) -> [Char] -> IO [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
h [Char] -> [Char] -> [Char]
</> [Char]
".ssh"

dotFile :: FilePath -> User -> IO FilePath
dotFile :: [Char] -> User -> IO [Char]
dotFile [Char]
f User
user = do
	[Char]
d <- User -> IO [Char]
dotDir User
user
	[Char] -> IO [Char]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Char] -> IO [Char]) -> [Char] -> IO [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
d [Char] -> [Char] -> [Char]
</> [Char]
f

-- | Makes the ssh server listen on a given port, in addition to any other
-- ports it is configured to listen on.
--
-- Revert to prevent it listening on a particular port.
listenPort :: Port -> RevertableProperty DebianLike DebianLike
listenPort :: Port -> RevertableProperty DebianLike DebianLike
listenPort Port
port = CombinedType (Property UnixLike) (Property DebianLike)
Property DebianLike
enable Property DebianLike
-> Property DebianLike -> RevertableProperty DebianLike DebianLike
forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> CombinedType (Property UnixLike) (Property DebianLike)
Property DebianLike
disable
  where
	portline :: [Char]
portline = [Char]
"Port " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Port -> [Char]
forall t. ConfigurableValue t => t -> [Char]
val Port
port
	enable :: CombinedType (Property UnixLike) (Property DebianLike)
enable = [Char]
sshdConfig [Char] -> [Char] -> Property UnixLike
`File.containsLine` [Char]
portline
		Property UnixLike -> [Char] -> Property UnixLike
forall p. IsProp p => p -> [Char] -> p
`describe` ([Char]
"ssh listening on " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
portline)
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
restarted
	disable :: CombinedType (Property UnixLike) (Property DebianLike)
disable = [Char]
sshdConfig [Char] -> [Char] -> Property UnixLike
`File.lacksLine` [Char]
portline
		Property UnixLike -> [Char] -> Property UnixLike
forall p. IsProp p => p -> [Char] -> p
`describe` ([Char]
"ssh not listening on " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
portline)
		Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
restarted

hasAuthorizedKeys :: User -> IO Bool
hasAuthorizedKeys :: User -> IO Bool
hasAuthorizedKeys = [Char] -> IO Bool
go ([Char] -> IO Bool) -> (User -> IO [Char]) -> User -> IO Bool
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< [Char] -> User -> IO [Char]
dotFile [Char]
"authorized_keys"
  where
	go :: [Char] -> IO Bool
go [Char]
f = Bool -> Bool
not (Bool -> Bool) -> ([Char] -> Bool) -> [Char] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Char] -> Bool) -> IO [Char] -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> IO [Char] -> IO [Char]
forall (m :: * -> *) a. MonadCatch m => a -> m a -> m a
catchDefaultIO [Char]
"" ([Char] -> IO [Char]
readFile [Char]
f)

-- | Blows away existing host keys and make new ones.
-- Useful for systems installed from an image that might reuse host keys.
-- A flag file is used to only ever do this once.
randomHostKeys :: Property DebianLike
randomHostKeys :: Property DebianLike
randomHostKeys = Property UnixLike -> [Char] -> Property UnixLike
forall i. Property i -> [Char] -> Property i
flagFile Property UnixLike
prop [Char]
"/etc/ssh/.unique_host_keys"
	Property UnixLike
-> Property DebianLike
-> CombinedType (Property UnixLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
restarted
  where
	prop :: Property UnixLike
	prop :: Property UnixLike
prop = [Char]
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
"ssh random host keys" ((OuterMetaTypesWitness
    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property UnixLike)
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> do
		Propellor Bool -> Propellor ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Propellor Bool -> Propellor ()) -> Propellor Bool -> Propellor ()
forall a b. (a -> b) -> a -> b
$ IO Bool -> Propellor Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Propellor Bool) -> IO Bool -> Propellor Bool
forall a b. (a -> b) -> a -> b
$ [Char] -> [CommandParam] -> IO Bool
boolSystem [Char]
"sh"
			[ [Char] -> CommandParam
Param [Char]
"-c"
			, [Char] -> CommandParam
Param [Char]
"rm -f /etc/ssh/ssh_host_*"
			]
		OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> 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,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ [[Char]] -> UncheckedProperty UnixLike
scriptProperty [ [Char]
"DPKG_MAINTSCRIPT_NAME=postinst DPKG_MAINTSCRIPT_PACKAGE=openssh-server /var/lib/dpkg/info/openssh-server.postinst configure" ]
			UncheckedProperty UnixLike -> Result -> Property UnixLike
forall (p :: * -> *) i.
Checkable p i =>
p i -> Result -> Property i
`assume` Result
MadeChange

-- | The text of a ssh public key, for example, "ssh-ed25519 AAAAC3NzaC1lZDI1NTE5AAAAIB3BJ2GqZiTR2LEoDXyYFgh/BduWefjdKXAsAtzS9zeI"
type PubKeyText = String

-- | Installs the specified list of ssh host keys.
--
-- The corresponding private keys come from the privdata.
--
-- Any host keys that are not in the list are removed from the host.
hostKeys :: IsContext c => c -> [(SshKeyType, PubKeyText)] -> Property (HasInfo + DebianLike)
hostKeys :: c -> [(SshKeyType, [Char])] -> Property (HasInfo + DebianLike)
hostKeys c
ctx [(SshKeyType, [Char])]
l = Property
  (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
Property (HasInfo + DebianLike)
go Property
  (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property DebianLike
-> CombinedType
     (Property
        (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
     (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` Property DebianLike
cleanup
  where
	desc :: [Char]
desc = [Char]
"ssh host keys configured " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [SshKeyType] -> [Char]
typelist (((SshKeyType, [Char]) -> SshKeyType)
-> [(SshKeyType, [Char])] -> [SshKeyType]
forall a b. (a -> b) -> [a] -> [b]
map (SshKeyType, [Char]) -> SshKeyType
forall a b. (a, b) -> a
fst [(SshKeyType, [Char])]
l)
	go :: Property (HasInfo + DebianLike)
	go :: Property (HasInfo + DebianLike)
go = [Char]
-> Props
     (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
propertyList [Char]
desc (Props
   (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Property
      (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> Props
     (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Property
     (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ [Property
   (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])]
-> Props
     (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall k (metatypes :: k).
[Property (MetaTypes metatypes)] -> Props (MetaTypes metatypes)
toProps ([Property
    (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])]
 -> Props
      (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
-> [Property
      (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])]
-> Props
     (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
forall a b. (a -> b) -> a -> b
$ [Maybe
   (Property
      (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))]
-> [Property
      (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe
    (Property
       (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))]
 -> [Property
       (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])])
-> [Maybe
      (Property
         (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))]
-> [Property
      (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])]
forall a b. (a -> b) -> a -> b
$
		((SshKeyType, [Char])
 -> Maybe
      (Property
         (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])))
-> [(SshKeyType, [Char])]
-> [Maybe
      (Property
         (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))]
forall a b. (a -> b) -> [a] -> [b]
map (\(SshKeyType
t, [Char]
pub) -> Property
  (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Maybe
     (Property
        (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a. a -> Maybe a
Just (Property
   (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
 -> Maybe
      (Property
         (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])))
-> Property
     (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish])
-> Maybe
     (Property
        (Sing '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish]))
forall a b. (a -> b) -> a -> b
$ c -> SshKeyType -> [Char] -> Property (HasInfo + DebianLike)
forall c.
IsContext c =>
c -> SshKeyType -> [Char] -> Property (HasInfo + DebianLike)
hostKey c
ctx SshKeyType
t [Char]
pub) [(SshKeyType, [Char])]
l
	typelist :: [SshKeyType] -> [Char]
typelist [SshKeyType]
tl = [Char]
"(" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unwords ((SshKeyType -> [Char]) -> [SshKeyType] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map SshKeyType -> [Char]
fromKeyType [SshKeyType]
tl) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
")"
	alltypes :: [SshKeyType]
alltypes = [SshKeyType
forall a. Bounded a => a
minBound..SshKeyType
forall a. Bounded a => a
maxBound]
	staletypes :: [SshKeyType]
staletypes = let have :: [SshKeyType]
have = ((SshKeyType, [Char]) -> SshKeyType)
-> [(SshKeyType, [Char])] -> [SshKeyType]
forall a b. (a -> b) -> [a] -> [b]
map (SshKeyType, [Char]) -> SshKeyType
forall a b. (a, b) -> a
fst [(SshKeyType, [Char])]
l in (SshKeyType -> Bool) -> [SshKeyType] -> [SshKeyType]
forall a. (a -> Bool) -> [a] -> [a]
filter (SshKeyType -> [SshKeyType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [SshKeyType]
have) [SshKeyType]
alltypes
	removestale :: Bool -> [Property DebianLike]
	removestale :: Bool -> [Property DebianLike]
removestale Bool
b = (SshKeyType -> Property DebianLike)
-> [SshKeyType] -> [Property DebianLike]
forall a b. (a -> b) -> [a] -> [b]
map (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)
-> (SshKeyType -> Property UnixLike)
-> SshKeyType
-> Property DebianLike
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> Property UnixLike
File.notPresent ([Char] -> Property UnixLike)
-> (SshKeyType -> [Char]) -> SshKeyType -> Property UnixLike
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SshKeyType -> Bool -> [Char]) -> Bool -> SshKeyType -> [Char]
forall a b c. (a -> b -> c) -> b -> a -> c
flip SshKeyType -> Bool -> [Char]
keyFile Bool
b) [SshKeyType]
staletypes
	cleanup :: Property DebianLike
	cleanup :: Property DebianLike
cleanup
		| [SshKeyType] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [SshKeyType]
staletypes Bool -> Bool -> Bool
|| [(SshKeyType, [Char])] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(SshKeyType, [Char])]
l = Property DebianLike
forall k (t :: k). SingI t => Property (MetaTypes t)
doNothing
		| Bool
otherwise =
			[Char] -> Props DebianLike -> Property DebianLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties ([Char]
"any other ssh host keys removed " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [SshKeyType] -> [Char]
typelist [SshKeyType]
staletypes)
				([Property DebianLike] -> Props DebianLike
forall k (metatypes :: k).
[Property (MetaTypes metatypes)] -> Props (MetaTypes metatypes)
toProps ([Property DebianLike] -> Props DebianLike)
-> [Property DebianLike] -> Props DebianLike
forall a b. (a -> b) -> a -> b
$ Bool -> [Property DebianLike]
removestale Bool
True [Property DebianLike]
-> [Property DebianLike] -> [Property DebianLike]
forall a. [a] -> [a] -> [a]
++ Bool -> [Property DebianLike]
removestale Bool
False)
				Property DebianLike
-> Property DebianLike
-> CombinedType (Property DebianLike) (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
restarted

-- | Installs a single ssh host key of a particular type.
--
-- The public key is provided to this function;
-- the private key comes from the privdata;
hostKey :: IsContext c => c -> SshKeyType -> PubKeyText -> Property (HasInfo + DebianLike)
hostKey :: c -> SshKeyType -> [Char] -> Property (HasInfo + DebianLike)
hostKey c
context SshKeyType
keytype [Char]
pub = Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
go Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property DebianLike
-> CombinedType
     (Property
        (MetaTypes
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
     (Property DebianLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`onChange` Property DebianLike
restarted
  where
	go :: Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
go = [Char]
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties [Char]
desc (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
		Props UnixLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, '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))
& SshKeyType -> [Char] -> Property (HasInfo + UnixLike)
hostPubKey SshKeyType
keytype [Char]
pub
		Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, '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))
& Property UnixLike
installpub
		Props
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
Property (HasInfo + UnixLike)
installpriv
	desc :: [Char]
desc = [Char]
"ssh host key configured (" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ SshKeyType -> [Char]
fromKeyType SshKeyType
keytype [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
")"
	keysrc :: [Char] -> PrivDataField -> PrivDataSource
keysrc [Char]
ext PrivDataField
field = PrivDataField -> [Char] -> [Char] -> PrivDataSource
PrivDataSourceFileFromCommand PrivDataField
field ([Char]
"sshkey"[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
ext)
		([Char]
"ssh-keygen -t " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ SshKeyType -> [Char]
sshKeyTypeParam SshKeyType
keytype [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" -f sshkey")
	installpub :: Property UnixLike
	installpub :: Property UnixLike
installpub = ([Char] -> [[Char]] -> Property UnixLike)
-> Bool -> [[Char]] -> Property UnixLike
keywriter [Char] -> [[Char]] -> Property UnixLike
File.hasContent Bool
True ([Char] -> [[Char]]
lines [Char]
pub)
	installpriv :: Property (HasInfo + UnixLike)
	installpriv :: Property (HasInfo + UnixLike)
installpriv = PrivDataSource
-> c
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property
         (MetaTypes
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
               'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall c s metatypes.
(IsContext c, IsPrivDataSource s,
 IncludesInfo metatypes ~ 'True) =>
s
-> c
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property metatypes)
-> Property metatypes
withPrivData ([Char] -> PrivDataField -> PrivDataSource
keysrc [Char]
"" (SshKeyType -> [Char] -> PrivDataField
SshPrivKey SshKeyType
keytype [Char]
"")) c
context ((((PrivData -> Propellor Result) -> Propellor Result)
  -> Property
       (MetaTypes
          '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
             'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property
         (MetaTypes
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
               'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$ \(PrivData -> Propellor Result) -> Propellor Result
getkey ->
		[Char]
-> (OuterMetaTypesWitness
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
desc ((OuterMetaTypesWitness
    '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> (OuterMetaTypesWitness
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> (PrivData -> Propellor Result) -> Propellor Result
getkey ((PrivData -> Propellor Result) -> Propellor Result)
-> (PrivData -> Propellor Result) -> Propellor Result
forall a b. (a -> b) -> a -> b
$
			OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> Property UnixLike -> Propellor Result
forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w
				(Property UnixLike -> Propellor Result)
-> (PrivData -> Property UnixLike) -> PrivData -> Propellor Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Char] -> [[Char]] -> Property UnixLike)
-> Bool -> [[Char]] -> Property UnixLike
keywriter [Char] -> [[Char]] -> Property UnixLike
File.hasContentProtected Bool
False
				([[Char]] -> Property UnixLike)
-> (PrivData -> [[Char]]) -> PrivData -> Property UnixLike
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PrivData -> [[Char]]
privDataLines
	keywriter :: ([Char] -> [[Char]] -> Property UnixLike)
-> Bool -> [[Char]] -> Property UnixLike
keywriter [Char] -> [[Char]] -> Property UnixLike
p Bool
ispub [[Char]]
keylines = do
		let f :: [Char]
f = SshKeyType -> Bool -> [Char]
keyFile SshKeyType
keytype Bool
ispub
		[Char] -> [[Char]] -> Property UnixLike
p [Char]
f ([[Char]] -> [[Char]]
keyFileContent [[Char]]
keylines)

-- Make sure that there is a newline at the end;
-- ssh requires this for some types of private keys.
keyFileContent :: [String] -> [File.Line]
keyFileContent :: [[Char]] -> [[Char]]
keyFileContent [[Char]]
keylines = [[Char]]
keylines [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]
""]

keyFile :: SshKeyType -> Bool -> FilePath
keyFile :: SshKeyType -> Bool -> [Char]
keyFile SshKeyType
keytype Bool
ispub = [Char]
"/etc/ssh/ssh_host_" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ SshKeyType -> [Char]
fromKeyType SshKeyType
keytype [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"_key" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
ext
  where
	ext :: [Char]
ext = if Bool
ispub then [Char]
".pub" else [Char]
""

-- | Indicates the host key that is used by a Host, but does not actually
-- configure the host to use it. Normally this does not need to be used;
-- use 'hostKey' instead.
hostPubKey :: SshKeyType -> PubKeyText -> Property (HasInfo + UnixLike)
hostPubKey :: SshKeyType -> [Char] -> Property (HasInfo + UnixLike)
hostPubKey SshKeyType
t = [Char] -> HostKeyInfo -> Property (HasInfo + UnixLike)
forall v. IsInfo v => [Char] -> v -> Property (HasInfo + UnixLike)
pureInfoProperty [Char]
"ssh pubkey known" (HostKeyInfo
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> ([Char] -> HostKeyInfo)
-> [Char]
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map SshKeyType [Char] -> HostKeyInfo
HostKeyInfo (Map SshKeyType [Char] -> HostKeyInfo)
-> ([Char] -> Map SshKeyType [Char]) -> [Char] -> HostKeyInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SshKeyType -> [Char] -> Map SshKeyType [Char]
forall k a. k -> a -> Map k a
M.singleton SshKeyType
t

getHostPubKey :: Propellor (M.Map SshKeyType PubKeyText)
getHostPubKey :: Propellor (Map SshKeyType [Char])
getHostPubKey = HostKeyInfo -> Map SshKeyType [Char]
fromHostKeyInfo (HostKeyInfo -> Map SshKeyType [Char])
-> Propellor HostKeyInfo -> Propellor (Map SshKeyType [Char])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Propellor HostKeyInfo
forall v. IsInfo v => Propellor v
askInfo

newtype HostKeyInfo = HostKeyInfo
	{ HostKeyInfo -> Map SshKeyType [Char]
fromHostKeyInfo :: M.Map SshKeyType PubKeyText }
	deriving (HostKeyInfo -> HostKeyInfo -> Bool
(HostKeyInfo -> HostKeyInfo -> Bool)
-> (HostKeyInfo -> HostKeyInfo -> Bool) -> Eq HostKeyInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HostKeyInfo -> HostKeyInfo -> Bool
$c/= :: HostKeyInfo -> HostKeyInfo -> Bool
== :: HostKeyInfo -> HostKeyInfo -> Bool
$c== :: HostKeyInfo -> HostKeyInfo -> Bool
Eq, Eq HostKeyInfo
Eq HostKeyInfo
-> (HostKeyInfo -> HostKeyInfo -> Ordering)
-> (HostKeyInfo -> HostKeyInfo -> Bool)
-> (HostKeyInfo -> HostKeyInfo -> Bool)
-> (HostKeyInfo -> HostKeyInfo -> Bool)
-> (HostKeyInfo -> HostKeyInfo -> Bool)
-> (HostKeyInfo -> HostKeyInfo -> HostKeyInfo)
-> (HostKeyInfo -> HostKeyInfo -> HostKeyInfo)
-> Ord HostKeyInfo
HostKeyInfo -> HostKeyInfo -> Bool
HostKeyInfo -> HostKeyInfo -> Ordering
HostKeyInfo -> HostKeyInfo -> HostKeyInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: HostKeyInfo -> HostKeyInfo -> HostKeyInfo
$cmin :: HostKeyInfo -> HostKeyInfo -> HostKeyInfo
max :: HostKeyInfo -> HostKeyInfo -> HostKeyInfo
$cmax :: HostKeyInfo -> HostKeyInfo -> HostKeyInfo
>= :: HostKeyInfo -> HostKeyInfo -> Bool
$c>= :: HostKeyInfo -> HostKeyInfo -> Bool
> :: HostKeyInfo -> HostKeyInfo -> Bool
$c> :: HostKeyInfo -> HostKeyInfo -> Bool
<= :: HostKeyInfo -> HostKeyInfo -> Bool
$c<= :: HostKeyInfo -> HostKeyInfo -> Bool
< :: HostKeyInfo -> HostKeyInfo -> Bool
$c< :: HostKeyInfo -> HostKeyInfo -> Bool
compare :: HostKeyInfo -> HostKeyInfo -> Ordering
$ccompare :: HostKeyInfo -> HostKeyInfo -> Ordering
$cp1Ord :: Eq HostKeyInfo
Ord, Typeable, Int -> HostKeyInfo -> [Char] -> [Char]
[HostKeyInfo] -> [Char] -> [Char]
HostKeyInfo -> [Char]
(Int -> HostKeyInfo -> [Char] -> [Char])
-> (HostKeyInfo -> [Char])
-> ([HostKeyInfo] -> [Char] -> [Char])
-> Show HostKeyInfo
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [HostKeyInfo] -> [Char] -> [Char]
$cshowList :: [HostKeyInfo] -> [Char] -> [Char]
show :: HostKeyInfo -> [Char]
$cshow :: HostKeyInfo -> [Char]
showsPrec :: Int -> HostKeyInfo -> [Char] -> [Char]
$cshowsPrec :: Int -> HostKeyInfo -> [Char] -> [Char]
Show)

instance IsInfo HostKeyInfo where
	propagateInfo :: HostKeyInfo -> PropagateInfo
propagateInfo HostKeyInfo
_ = Bool -> PropagateInfo
PropagateInfo Bool
False

instance Sem.Semigroup HostKeyInfo where
	HostKeyInfo Map SshKeyType [Char]
old <> :: HostKeyInfo -> HostKeyInfo -> HostKeyInfo
<> HostKeyInfo Map SshKeyType [Char]
new =
		-- new first because union prefers values from the first
		-- parameter when there is a duplicate key
		Map SshKeyType [Char] -> HostKeyInfo
HostKeyInfo (Map SshKeyType [Char]
new Map SshKeyType [Char]
-> Map SshKeyType [Char] -> Map SshKeyType [Char]
forall k a. Ord k => Map k a -> Map k a -> Map k a
`M.union` Map SshKeyType [Char]
old)

instance Monoid HostKeyInfo where
	mempty :: HostKeyInfo
mempty = Map SshKeyType [Char] -> HostKeyInfo
HostKeyInfo Map SshKeyType [Char]
forall k a. Map k a
M.empty
	mappend :: HostKeyInfo -> HostKeyInfo -> HostKeyInfo
mappend = HostKeyInfo -> HostKeyInfo -> HostKeyInfo
forall a. Semigroup a => a -> a -> a
(Sem.<>)

userPubKeys :: User -> [(SshKeyType, PubKeyText)] -> Property (HasInfo + UnixLike)
userPubKeys :: User -> [(SshKeyType, [Char])] -> Property (HasInfo + UnixLike)
userPubKeys u :: User
u@(User [Char]
n) [(SshKeyType, [Char])]
l = [Char] -> UserKeyInfo -> Property (HasInfo + UnixLike)
forall v. IsInfo v => [Char] -> v -> Property (HasInfo + UnixLike)
pureInfoProperty ([Char]
"ssh pubkey for " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
n) (UserKeyInfo -> Property (HasInfo + UnixLike))
-> UserKeyInfo -> Property (HasInfo + UnixLike)
forall a b. (a -> b) -> a -> b
$
	Map User (Set (SshKeyType, [Char])) -> UserKeyInfo
UserKeyInfo (User
-> Set (SshKeyType, [Char]) -> Map User (Set (SshKeyType, [Char]))
forall k a. k -> a -> Map k a
M.singleton User
u ([(SshKeyType, [Char])] -> Set (SshKeyType, [Char])
forall a. Ord a => [a] -> Set a
S.fromList [(SshKeyType, [Char])]
l))

getUserPubKeys :: User -> Propellor [(SshKeyType, PubKeyText)]
getUserPubKeys :: User -> Propellor [(SshKeyType, [Char])]
getUserPubKeys User
u = [(SshKeyType, [Char])]
-> (Set (SshKeyType, [Char]) -> [(SshKeyType, [Char])])
-> Maybe (Set (SshKeyType, [Char]))
-> [(SshKeyType, [Char])]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Set (SshKeyType, [Char]) -> [(SshKeyType, [Char])]
forall a. Set a -> [a]
S.toList (Maybe (Set (SshKeyType, [Char])) -> [(SshKeyType, [Char])])
-> (UserKeyInfo -> Maybe (Set (SshKeyType, [Char])))
-> UserKeyInfo
-> [(SshKeyType, [Char])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. User
-> Map User (Set (SshKeyType, [Char]))
-> Maybe (Set (SshKeyType, [Char]))
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup User
u (Map User (Set (SshKeyType, [Char]))
 -> Maybe (Set (SshKeyType, [Char])))
-> (UserKeyInfo -> Map User (Set (SshKeyType, [Char])))
-> UserKeyInfo
-> Maybe (Set (SshKeyType, [Char]))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserKeyInfo -> Map User (Set (SshKeyType, [Char]))
fromUserKeyInfo (UserKeyInfo -> [(SshKeyType, [Char])])
-> Propellor UserKeyInfo -> Propellor [(SshKeyType, [Char])]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Propellor UserKeyInfo
forall v. IsInfo v => Propellor v
askInfo

newtype UserKeyInfo = UserKeyInfo
	{ UserKeyInfo -> Map User (Set (SshKeyType, [Char]))
fromUserKeyInfo :: M.Map User (S.Set (SshKeyType, PubKeyText)) }
	deriving (UserKeyInfo -> UserKeyInfo -> Bool
(UserKeyInfo -> UserKeyInfo -> Bool)
-> (UserKeyInfo -> UserKeyInfo -> Bool) -> Eq UserKeyInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserKeyInfo -> UserKeyInfo -> Bool
$c/= :: UserKeyInfo -> UserKeyInfo -> Bool
== :: UserKeyInfo -> UserKeyInfo -> Bool
$c== :: UserKeyInfo -> UserKeyInfo -> Bool
Eq, Eq UserKeyInfo
Eq UserKeyInfo
-> (UserKeyInfo -> UserKeyInfo -> Ordering)
-> (UserKeyInfo -> UserKeyInfo -> Bool)
-> (UserKeyInfo -> UserKeyInfo -> Bool)
-> (UserKeyInfo -> UserKeyInfo -> Bool)
-> (UserKeyInfo -> UserKeyInfo -> Bool)
-> (UserKeyInfo -> UserKeyInfo -> UserKeyInfo)
-> (UserKeyInfo -> UserKeyInfo -> UserKeyInfo)
-> Ord UserKeyInfo
UserKeyInfo -> UserKeyInfo -> Bool
UserKeyInfo -> UserKeyInfo -> Ordering
UserKeyInfo -> UserKeyInfo -> UserKeyInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UserKeyInfo -> UserKeyInfo -> UserKeyInfo
$cmin :: UserKeyInfo -> UserKeyInfo -> UserKeyInfo
max :: UserKeyInfo -> UserKeyInfo -> UserKeyInfo
$cmax :: UserKeyInfo -> UserKeyInfo -> UserKeyInfo
>= :: UserKeyInfo -> UserKeyInfo -> Bool
$c>= :: UserKeyInfo -> UserKeyInfo -> Bool
> :: UserKeyInfo -> UserKeyInfo -> Bool
$c> :: UserKeyInfo -> UserKeyInfo -> Bool
<= :: UserKeyInfo -> UserKeyInfo -> Bool
$c<= :: UserKeyInfo -> UserKeyInfo -> Bool
< :: UserKeyInfo -> UserKeyInfo -> Bool
$c< :: UserKeyInfo -> UserKeyInfo -> Bool
compare :: UserKeyInfo -> UserKeyInfo -> Ordering
$ccompare :: UserKeyInfo -> UserKeyInfo -> Ordering
$cp1Ord :: Eq UserKeyInfo
Ord, Typeable, Int -> UserKeyInfo -> [Char] -> [Char]
[UserKeyInfo] -> [Char] -> [Char]
UserKeyInfo -> [Char]
(Int -> UserKeyInfo -> [Char] -> [Char])
-> (UserKeyInfo -> [Char])
-> ([UserKeyInfo] -> [Char] -> [Char])
-> Show UserKeyInfo
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
showList :: [UserKeyInfo] -> [Char] -> [Char]
$cshowList :: [UserKeyInfo] -> [Char] -> [Char]
show :: UserKeyInfo -> [Char]
$cshow :: UserKeyInfo -> [Char]
showsPrec :: Int -> UserKeyInfo -> [Char] -> [Char]
$cshowsPrec :: Int -> UserKeyInfo -> [Char] -> [Char]
Show)

instance IsInfo UserKeyInfo where
	propagateInfo :: UserKeyInfo -> PropagateInfo
propagateInfo UserKeyInfo
_ = Bool -> PropagateInfo
PropagateInfo Bool
False

instance Sem.Semigroup UserKeyInfo where
	UserKeyInfo Map User (Set (SshKeyType, [Char]))
old <> :: UserKeyInfo -> UserKeyInfo -> UserKeyInfo
<> UserKeyInfo Map User (Set (SshKeyType, [Char]))
new =
		Map User (Set (SshKeyType, [Char])) -> UserKeyInfo
UserKeyInfo ((Set (SshKeyType, [Char])
 -> Set (SshKeyType, [Char]) -> Set (SshKeyType, [Char]))
-> Map User (Set (SshKeyType, [Char]))
-> Map User (Set (SshKeyType, [Char]))
-> Map User (Set (SshKeyType, [Char]))
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
M.unionWith Set (SshKeyType, [Char])
-> Set (SshKeyType, [Char]) -> Set (SshKeyType, [Char])
forall a. Ord a => Set a -> Set a -> Set a
S.union Map User (Set (SshKeyType, [Char]))
old Map User (Set (SshKeyType, [Char]))
new)

instance Monoid UserKeyInfo where
	mempty :: UserKeyInfo
mempty = Map User (Set (SshKeyType, [Char])) -> UserKeyInfo
UserKeyInfo Map User (Set (SshKeyType, [Char]))
forall k a. Map k a
M.empty
	mappend :: UserKeyInfo -> UserKeyInfo -> UserKeyInfo
mappend = UserKeyInfo -> UserKeyInfo -> UserKeyInfo
forall a. Semigroup a => a -> a -> a
(Sem.<>)

-- | Sets up a user with the specified public keys, and the corresponding
-- private keys from the privdata.
--
-- The public keys are added to the Info, so other properties like
-- `authorizedKeysFrom` can use them.
userKeys :: IsContext c => User -> c -> [(SshKeyType, PubKeyText)] -> Property (HasInfo + UnixLike)
userKeys :: User
-> c -> [(SshKeyType, [Char])] -> Property (HasInfo + UnixLike)
userKeys user :: User
user@(User [Char]
name) c
context [(SshKeyType, [Char])]
ks = [Char]
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties [Char]
desc (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$ [Property
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])]
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall k (metatypes :: k).
[Property (MetaTypes metatypes)] -> Props (MetaTypes metatypes)
toProps ([Property
    (MetaTypes
       '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
          'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])]
 -> Props
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> [Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])]
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$
	User -> [(SshKeyType, [Char])] -> Property (HasInfo + UnixLike)
userPubKeys User
user [(SshKeyType, [Char])]
ks Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> [Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])]
-> [Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])]
forall a. a -> [a] -> [a]
: ((SshKeyType, [Char])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> [(SshKeyType, [Char])]
-> [Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe [Char]
-> User
-> c
-> (SshKeyType, [Char])
-> Property (HasInfo + UnixLike)
forall c.
IsContext c =>
Maybe [Char]
-> User
-> c
-> (SshKeyType, [Char])
-> Property (HasInfo + UnixLike)
userKeyAt Maybe [Char]
forall a. Maybe a
Nothing User
user c
context) [(SshKeyType, [Char])]
ks
  where
	desc :: [Char]
desc = [[Char]] -> [Char]
unwords
		[ [Char]
name
		, [Char]
"has ssh key"
		, [Char]
"(" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [[Char]] -> [Char]
unwords (((SshKeyType, [Char]) -> [Char])
-> [(SshKeyType, [Char])] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (SshKeyType -> [Char]
fromKeyType (SshKeyType -> [Char])
-> ((SshKeyType, [Char]) -> SshKeyType)
-> (SshKeyType, [Char])
-> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SshKeyType, [Char]) -> SshKeyType
forall a b. (a, b) -> a
fst) [(SshKeyType, [Char])]
ks) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
")"
		]

-- | Sets up a user with the specified pubic key, and a private
-- key from the privdata.
--
-- A FilePath can be specified to write the key to somewhere other than
-- the default locations. Allows a user to have multiple keys for
-- different roles.
--
-- When the FilePath is relative, is put inside the User's 
-- ~/.ssh/ directory.
userKeyAt :: IsContext c => Maybe FilePath -> User -> c -> (SshKeyType, PubKeyText) -> Property (HasInfo + UnixLike)
userKeyAt :: Maybe [Char]
-> User
-> c
-> (SshKeyType, [Char])
-> Property (HasInfo + UnixLike)
userKeyAt Maybe [Char]
dest user :: User
user@(User [Char]
u) c
context (SshKeyType
keytype, [Char]
pubkeytext) =
	[Char]
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties [Char]
desc (Props
   (MetaTypes
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Props
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
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))
& Property UnixLike
pubkey
		Props UnixLike
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& Property
  (MetaTypes
     '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
        'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
Property (HasInfo + UnixLike)
privkey
  where
	desc :: [Char]
desc = [[Char]] -> [Char]
unwords ([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$ [Maybe [Char]] -> [[Char]]
forall a. [Maybe a] -> [a]
catMaybes
		[ [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
u
		, [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
"has ssh key"
		, Maybe [Char]
dest
		, [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just ([Char] -> Maybe [Char]) -> [Char] -> Maybe [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
"(" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ SshKeyType -> [Char]
fromKeyType SshKeyType
keytype [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
")"
		]
	pubkey :: Property UnixLike
	pubkey :: Property UnixLike
pubkey = [Char]
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
desc ((OuterMetaTypesWitness
    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property UnixLike)
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> 
		OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> 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,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Propellor (Property UnixLike) -> Propellor Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ([Char] -> [[Char]] -> Property UnixLike)
-> [Char] -> [[Char]] -> Propellor (Property UnixLike)
installprop [Char] -> [[Char]] -> Property UnixLike
File.hasContent [Char]
".pub" [[Char]
pubkeytext]
	privkey :: Property (HasInfo + UnixLike)
	privkey :: Property (HasInfo + UnixLike)
privkey = PrivDataField
-> c
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property
         (MetaTypes
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
               'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall c s metatypes.
(IsContext c, IsPrivDataSource s,
 IncludesInfo metatypes ~ 'True) =>
s
-> c
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property metatypes)
-> Property metatypes
withPrivData (SshKeyType -> [Char] -> PrivDataField
SshPrivKey SshKeyType
keytype [Char]
u) c
context ((PrivData -> Propellor Result) -> Propellor Result)
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
((PrivData -> Propellor Result) -> Propellor Result)
-> Property (HasInfo + UnixLike)
privkey'
	privkey' :: ((PrivData -> Propellor Result) -> Propellor Result) -> Property (HasInfo + UnixLike)
	privkey' :: ((PrivData -> Propellor Result) -> Propellor Result)
-> Property (HasInfo + UnixLike)
privkey' (PrivData -> Propellor Result) -> Propellor Result
getkey = [Char]
-> (OuterMetaTypesWitness
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
desc ((OuterMetaTypesWitness
    '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> (OuterMetaTypesWitness
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> (PrivData -> Propellor Result) -> Propellor Result
getkey ((PrivData -> Propellor Result) -> Propellor Result)
-> (PrivData -> Propellor Result) -> Propellor Result
forall a b. (a -> b) -> a -> b
$ \PrivData
k ->
		OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> Property UnixLike -> Propellor Result
forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w
			(Property UnixLike -> Propellor Result)
-> Propellor (Property UnixLike) -> Propellor Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ([Char] -> [[Char]] -> Property UnixLike)
-> [Char] -> [[Char]] -> Propellor (Property UnixLike)
installprop [Char] -> [[Char]] -> Property UnixLike
File.hasContentProtected [Char]
"" (PrivData -> [[Char]]
privDataLines PrivData
k)
	installprop :: ([Char] -> [[Char]] -> Property UnixLike)
-> [Char] -> [[Char]] -> Propellor (Property UnixLike)
installprop [Char] -> [[Char]] -> Property UnixLike
writer [Char]
ext [[Char]]
key = do
		[Char]
f <- IO [Char] -> Propellor [Char]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> Propellor [Char]) -> IO [Char] -> Propellor [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> IO [Char]
keyfile [Char]
ext
		Property UnixLike -> Propellor (Property UnixLike)
forall (m :: * -> *) a. Monad m => a -> m a
return (Property UnixLike -> Propellor (Property UnixLike))
-> Property UnixLike -> Propellor (Property UnixLike)
forall a b. (a -> b) -> a -> b
$ [Char] -> Props UnixLike -> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties [Char]
desc (Props UnixLike -> Property UnixLike)
-> Props UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
			Props UnixLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Char] -> Property UnixLike
File.dirExists ([Char] -> [Char]
takeDirectory [Char]
f)
			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))
& [Char] -> [[Char]] -> Property UnixLike
writer [Char]
f ([[Char]] -> [[Char]]
keyFileContent [[Char]]
key)
			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))
& [Char] -> User -> Group -> Property UnixLike
File.ownerGroup [Char]
f User
user (User -> Group
userGroup User
user)
			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))
& [Char] -> User -> Group -> Property UnixLike
File.ownerGroup ([Char] -> [Char]
takeDirectory [Char]
f) User
user (User -> Group
userGroup User
user)
	keyfile :: [Char] -> IO [Char]
keyfile [Char]
ext = case Maybe [Char]
dest of
		Maybe [Char]
Nothing -> [Char] -> IO [Char]
relhomessh ([Char] -> IO [Char]) -> [Char] -> IO [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
"id_" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ SshKeyType -> [Char]
fromKeyType SshKeyType
keytype [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
ext
		Just [Char]
f
			| [Char] -> Bool
isRelative [Char]
f -> [Char] -> IO [Char]
relhomessh ([Char]
f [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
ext)
			| Bool
otherwise -> [Char] -> IO [Char]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Char]
f [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
ext)
	relhomessh :: [Char] -> IO [Char]
relhomessh [Char]
f = do
		[Char]
home <- UserEntry -> [Char]
homeDirectory (UserEntry -> [Char]) -> IO UserEntry -> IO [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Char] -> IO UserEntry
getUserEntryForName [Char]
u
		[Char] -> IO [Char]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Char] -> IO [Char]) -> [Char] -> IO [Char]
forall a b. (a -> b) -> a -> b
$ [Char]
home [Char] -> [Char] -> [Char]
</> [Char]
".ssh" [Char] -> [Char] -> [Char]
</> [Char]
f

fromKeyType :: SshKeyType -> String
fromKeyType :: SshKeyType -> [Char]
fromKeyType SshKeyType
SshRsa = [Char]
"rsa"
fromKeyType SshKeyType
SshDsa = [Char]
"dsa"
fromKeyType SshKeyType
SshEcdsa = [Char]
"ecdsa"
fromKeyType SshKeyType
SshEd25519 = [Char]
"ed25519"

-- | Puts some host's ssh public key(s), as set using `hostPubKey`
-- or `hostKey` into the known_hosts file for a user.
knownHost :: [Host] -> HostName -> User -> Property UnixLike
knownHost :: [Host] -> [Char] -> User -> Property UnixLike
knownHost [Host]
hosts [Char]
hn user :: User
user@(User [Char]
u) = [Char]
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
desc ((OuterMetaTypesWitness
    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property UnixLike)
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w ->
	OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> [[Char]] -> Propellor Result
go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w ([[Char]] -> Propellor Result)
-> Propellor [[Char]] -> Propellor Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Host] -> [Char] -> Propellor [[Char]]
knownHostLines [Host]
hosts [Char]
hn
  where
	desc :: [Char]
desc = [Char]
u [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" knows ssh key for " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
hn

	go :: OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> [[Char]] -> Propellor Result
go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
_ [] = do
		[Char] -> Propellor ()
forall (m :: * -> *). MonadIO m => [Char] -> m ()
warningMessage ([Char] -> Propellor ()) -> [Char] -> Propellor ()
forall a b. (a -> b) -> a -> b
$ [Char]
"no configured ssh host keys for " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
hn
		Result -> Propellor Result
forall (m :: * -> *) a. Monad m => a -> m a
return Result
FailedChange
	go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w [[Char]]
ls = do
		[Char]
f <- IO [Char] -> Propellor [Char]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> Propellor [Char]) -> IO [Char] -> Propellor [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> User -> IO [Char]
dotFile [Char]
"known_hosts" User
user
		OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> 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,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ User -> [Char] -> Property UnixLike -> Property UnixLike
modKnownHost User
user [Char]
f (Property UnixLike -> Property UnixLike)
-> Property UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$
			[Char]
f [Char] -> [[Char]] -> Property UnixLike
`File.containsLines` [[Char]]
ls
				Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Char] -> Property UnixLike
File.dirExists ([Char] -> [Char]
takeDirectory [Char]
f)

-- | Reverts `knownHost`
unknownHost :: [Host] -> HostName -> User -> Property UnixLike
unknownHost :: [Host] -> [Char] -> User -> Property UnixLike
unknownHost [Host]
hosts [Char]
hn user :: User
user@(User [Char]
u) = [Char]
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
desc ((OuterMetaTypesWitness
    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property UnixLike)
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w ->
	OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> [[Char]] -> Propellor Result
go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w ([[Char]] -> Propellor Result)
-> Propellor [[Char]] -> Propellor Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Host] -> [Char] -> Propellor [[Char]]
knownHostLines [Host]
hosts [Char]
hn
  where
	desc :: [Char]
desc = [Char]
u [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" does not know ssh key for " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
hn

	go :: OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> [[Char]] -> Propellor Result
go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
_ [] = Result -> Propellor Result
forall (m :: * -> *) a. Monad m => a -> m a
return Result
NoChange
	go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w [[Char]]
ls = do
		[Char]
f <- IO [Char] -> Propellor [Char]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> Propellor [Char]) -> IO [Char] -> Propellor [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> User -> IO [Char]
dotFile [Char]
"known_hosts" User
user
		Propellor Bool
-> (Propellor Result, Propellor Result) -> Propellor Result
forall (m :: * -> *) a. Monad m => m Bool -> (m a, m a) -> m a
ifM (IO Bool -> Propellor Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Propellor Bool) -> IO Bool -> Propellor Bool
forall a b. (a -> b) -> a -> b
$ [Char] -> IO Bool
doesFileExist [Char]
f)
			( OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> 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,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ User -> [Char] -> Property UnixLike -> Property UnixLike
modKnownHost User
user [Char]
f (Property UnixLike -> Property UnixLike)
-> Property UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$
				[Char]
f [Char] -> [[Char]] -> Property UnixLike
`File.lacksLines` [[Char]]
ls
			, Result -> Propellor Result
forall (m :: * -> *) a. Monad m => a -> m a
return Result
NoChange
			)

knownHostLines :: [Host] -> HostName -> Propellor [File.Line]
knownHostLines :: [Host] -> [Char] -> Propellor [[Char]]
knownHostLines [Host]
hosts [Char]
hn = Maybe (Map SshKeyType [Char]) -> [[Char]]
keylines (Maybe (Map SshKeyType [Char]) -> [[Char]])
-> Propellor (Maybe (Map SshKeyType [Char])) -> Propellor [[Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Host]
-> [Char]
-> Propellor (Map SshKeyType [Char])
-> Propellor (Maybe (Map SshKeyType [Char]))
forall a. [Host] -> [Char] -> Propellor a -> Propellor (Maybe a)
fromHost [Host]
hosts [Char]
hn Propellor (Map SshKeyType [Char])
getHostPubKey
  where
	keylines :: Maybe (Map SshKeyType [Char]) -> [[Char]]
keylines (Just Map SshKeyType [Char]
m) = ([Char] -> [Char]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (\[Char]
k -> [Char]
hn [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
k) (Map SshKeyType [Char] -> [[Char]]
forall k a. Map k a -> [a]
M.elems Map SshKeyType [Char]
m)
	keylines Maybe (Map SshKeyType [Char])
Nothing = []

modKnownHost :: User -> FilePath -> Property UnixLike -> Property UnixLike
modKnownHost :: User -> [Char] -> Property UnixLike -> Property UnixLike
modKnownHost User
user [Char]
f Property UnixLike
p = Property UnixLike
p
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` [Char] -> User -> Group -> Property UnixLike
File.ownerGroup [Char]
f User
user (User -> Group
userGroup User
user)
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` [Char] -> User -> Group -> Property UnixLike
File.ownerGroup ([Char] -> [Char]
takeDirectory [Char]
f) User
user (User -> Group
userGroup User
user)

-- | Ensures that a local user's authorized_keys contains lines allowing
-- logins from a remote user on the specified Host.
--
-- The ssh keys of the remote user can be set using `userKeys`
--
-- Any other lines in the authorized_keys file are preserved as-is.
authorizedKeysFrom :: User -> (User, Host) -> Property UnixLike
localuser :: User
localuser@(User [Char]
ln) authorizedKeysFrom :: User -> (User, Host) -> Property UnixLike
`authorizedKeysFrom` (remoteuser :: User
remoteuser@(User [Char]
rn), Host
remotehost) =
	[Char]
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
desc (\OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> [[Char]] -> Propellor Result
go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w ([[Char]] -> Propellor Result)
-> Propellor [[Char]] -> Propellor Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< User -> Host -> Propellor [[Char]]
authorizedKeyLines User
remoteuser Host
remotehost)
  where
	remote :: [Char]
remote = [Char]
rn [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"@" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Host -> [Char]
hostName Host
remotehost
	desc :: [Char]
desc = [Char]
ln [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" authorized_keys from " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
remote

	go :: OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> [[Char]] -> Propellor Result
go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
_ [] = do
		[Char] -> Propellor ()
forall (m :: * -> *). MonadIO m => [Char] -> m ()
warningMessage ([Char] -> Propellor ()) -> [Char] -> Propellor ()
forall a b. (a -> b) -> a -> b
$ [Char]
"no configured ssh user keys for " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
remote
		Result -> Propellor Result
forall (m :: * -> *) a. Monad m => a -> m a
return Result
FailedChange
	go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w [[Char]]
ls = OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> 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,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ [Char] -> Props UnixLike -> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties [Char]
desc (Props UnixLike -> Property UnixLike)
-> Props UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$ [Property UnixLike] -> Props UnixLike
forall k (metatypes :: k).
[Property (MetaTypes metatypes)] -> Props (MetaTypes metatypes)
toProps ([Property UnixLike] -> Props UnixLike)
-> [Property UnixLike] -> Props UnixLike
forall a b. (a -> b) -> a -> b
$
		([Char] -> Property UnixLike) -> [[Char]] -> [Property UnixLike]
forall a b. (a -> b) -> [a] -> [b]
map (RevertableProperty UnixLike UnixLike -> Property UnixLike
forall setupmetatypes undometatypes.
RevertableProperty setupmetatypes undometatypes
-> Property setupmetatypes
setupRevertableProperty (RevertableProperty UnixLike UnixLike -> Property UnixLike)
-> ([Char] -> RevertableProperty UnixLike UnixLike)
-> [Char]
-> Property UnixLike
forall b c a. (b -> c) -> (a -> b) -> a -> c
. User -> [Char] -> RevertableProperty UnixLike UnixLike
authorizedKey User
localuser) [[Char]]
ls

-- | Reverts `authorizedKeysFrom`
unauthorizedKeysFrom :: User -> (User, Host) -> Property UnixLike
localuser :: User
localuser@(User [Char]
ln) unauthorizedKeysFrom :: User -> (User, Host) -> Property UnixLike
`unauthorizedKeysFrom` (remoteuser :: User
remoteuser@(User [Char]
rn), Host
remotehost) =
	[Char]
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
desc (\OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> [[Char]] -> Propellor Result
go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w ([[Char]] -> Propellor Result)
-> Propellor [[Char]] -> Propellor Result
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< User -> Host -> Propellor [[Char]]
authorizedKeyLines User
remoteuser Host
remotehost)
  where
	remote :: [Char]
remote = [Char]
rn [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"@" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Host -> [Char]
hostName Host
remotehost
	desc :: [Char]
desc = [Char]
ln [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" unauthorized_keys from " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
remote

	go :: OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> [[Char]] -> Propellor Result
go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
_ [] = Result -> Propellor Result
forall (m :: * -> *) a. Monad m => a -> m a
return Result
NoChange
	go OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w [[Char]]
ls = OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> 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,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ [Char] -> Props UnixLike -> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties [Char]
desc (Props UnixLike -> Property UnixLike)
-> Props UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$ [Property UnixLike] -> Props UnixLike
forall k (metatypes :: k).
[Property (MetaTypes metatypes)] -> Props (MetaTypes metatypes)
toProps ([Property UnixLike] -> Props UnixLike)
-> [Property UnixLike] -> Props UnixLike
forall a b. (a -> b) -> a -> b
$
		([Char] -> Property UnixLike) -> [[Char]] -> [Property UnixLike]
forall a b. (a -> b) -> [a] -> [b]
map (RevertableProperty UnixLike UnixLike -> Property UnixLike
forall setupmetatypes undometatypes.
RevertableProperty setupmetatypes undometatypes
-> Property undometatypes
undoRevertableProperty (RevertableProperty UnixLike UnixLike -> Property UnixLike)
-> ([Char] -> RevertableProperty UnixLike UnixLike)
-> [Char]
-> Property UnixLike
forall b c a. (b -> c) -> (a -> b) -> a -> c
. User -> [Char] -> RevertableProperty UnixLike UnixLike
authorizedKey User
localuser) [[Char]]
ls

authorizedKeyLines :: User -> Host -> Propellor [File.Line]
authorizedKeyLines :: User -> Host -> Propellor [[Char]]
authorizedKeyLines User
remoteuser Host
remotehost =
	((SshKeyType, [Char]) -> [Char])
-> [(SshKeyType, [Char])] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (SshKeyType, [Char]) -> [Char]
forall a b. (a, b) -> b
snd ([(SshKeyType, [Char])] -> [[Char]])
-> Propellor [(SshKeyType, [Char])] -> Propellor [[Char]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Host
-> Propellor [(SshKeyType, [Char])]
-> Propellor [(SshKeyType, [Char])]
forall a. Host -> Propellor a -> Propellor a
fromHost' Host
remotehost (User -> Propellor [(SshKeyType, [Char])]
getUserPubKeys User
remoteuser)

-- | Makes a user have authorized_keys from the PrivData
--
-- This removes any other lines from the file.
authorizedKeys :: IsContext c => User -> c -> Property (HasInfo + UnixLike)
authorizedKeys :: User -> c -> Property (HasInfo + UnixLike)
authorizedKeys user :: User
user@(User [Char]
u) c
context = PrivDataField
-> c
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property
         (MetaTypes
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
               'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall c s metatypes.
(IsContext c, IsPrivDataSource s,
 IncludesInfo metatypes ~ 'True) =>
s
-> c
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property metatypes)
-> Property metatypes
withPrivData ([Char] -> PrivDataField
SshAuthorizedKeys [Char]
u) c
context ((((PrivData -> Propellor Result) -> Propellor Result)
  -> Property
       (MetaTypes
          '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
             'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> (((PrivData -> Propellor Result) -> Propellor Result)
    -> Property
         (MetaTypes
            '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
               'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$ \(PrivData -> Propellor Result) -> Propellor Result
get ->
	[Char]
-> (OuterMetaTypesWitness
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' [Char]
desc ((OuterMetaTypesWitness
    '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property
      (MetaTypes
         '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
            'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
-> (OuterMetaTypesWitness
      '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property
     (MetaTypes
        '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
           'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD])
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> (PrivData -> Propellor Result) -> Propellor Result
get ((PrivData -> Propellor Result) -> Propellor Result)
-> (PrivData -> Propellor Result) -> Propellor Result
forall a b. (a -> b) -> a -> b
$ \PrivData
v -> do
		[Char]
f <- IO [Char] -> Propellor [Char]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> Propellor [Char]) -> IO [Char] -> Propellor [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> User -> IO [Char]
dotFile [Char]
"authorized_keys" User
user
		OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> Property UnixLike -> Propellor Result
forall (inner :: [MetaType]) (outer :: [MetaType]).
EnsurePropertyAllowed inner outer =>
OuterMetaTypesWitness outer
-> Property (MetaTypes inner) -> Propellor Result
ensureProperty OuterMetaTypesWitness
  '[ 'WithInfo, 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ [Char] -> Props UnixLike -> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> Props (MetaTypes metatypes) -> Property (MetaTypes metatypes)
combineProperties [Char]
desc (Props UnixLike -> Property UnixLike)
-> Props UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$ Props UnixLike
props
			Props UnixLike
-> Property UnixLike
-> Props
     (MetaTypes
        (Combine
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
           '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
              'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]))
forall a p (y :: [a]) (x :: [a]).
(IsProp p, MetaTypes y ~ GetMetaTypes p,
 CheckCombinableNote x y (NoteFor ('Text "&"))) =>
Props (MetaTypes x) -> p -> Props (MetaTypes (Combine x y))
& [Char] -> [[Char]] -> Property UnixLike
File.hasContentProtected [Char]
f ([[Char]] -> [[Char]]
keyFileContent (PrivData -> [[Char]]
privDataLines PrivData
v))
			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))
& [Char] -> User -> Group -> Property UnixLike
File.ownerGroup [Char]
f User
user (User -> Group
userGroup User
user)
			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))
& [Char] -> User -> Group -> Property UnixLike
File.ownerGroup ([Char] -> [Char]
takeDirectory [Char]
f) User
user (User -> Group
userGroup User
user)
  where
	desc :: [Char]
desc = [Char]
u [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" has authorized_keys"

-- | Ensures that a user's authorized_keys contains a line.
-- Any other lines in the file are preserved as-is.
authorizedKey :: User -> String -> RevertableProperty UnixLike UnixLike
authorizedKey :: User -> [Char] -> RevertableProperty UnixLike UnixLike
authorizedKey user :: User
user@(User [Char]
u) [Char]
l = Property UnixLike
add Property UnixLike
-> Property UnixLike -> RevertableProperty UnixLike UnixLike
forall setupmetatypes undometatypes.
Property setupmetatypes
-> Property undometatypes
-> RevertableProperty setupmetatypes undometatypes
<!> Property UnixLike
remove
  where
	add :: Property UnixLike
add = [Char]
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' ([Char]
u [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" has authorized_keys") ((OuterMetaTypesWitness
    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property UnixLike)
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> do
		[Char]
f <- IO [Char] -> Propellor [Char]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> Propellor [Char]) -> IO [Char] -> Propellor [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> User -> IO [Char]
dotFile [Char]
"authorized_keys" User
user
		OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> 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,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ [Char] -> User -> Property UnixLike -> Property UnixLike
modAuthorizedKey [Char]
f User
user (Property UnixLike -> Property UnixLike)
-> Property UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$
			[Char]
f [Char] -> [Char] -> Property UnixLike
`File.containsLine` [Char]
l
				Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`requires` [Char] -> Property UnixLike
File.dirExists ([Char] -> [Char]
takeDirectory [Char]
f)
	remove :: Property UnixLike
remove = [Char]
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall k (metatypes :: k).
SingI metatypes =>
[Char]
-> (OuterMetaTypesWitness metatypes -> Propellor Result)
-> Property (MetaTypes metatypes)
property' ([Char]
u [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" lacks authorized_keys") ((OuterMetaTypesWitness
    '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
       'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
  -> Propellor Result)
 -> Property UnixLike)
-> (OuterMetaTypesWitness
      '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
         'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
    -> Propellor Result)
-> Property UnixLike
forall a b. (a -> b) -> a -> b
$ \OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w -> do
		[Char]
f <- IO [Char] -> Propellor [Char]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> Propellor [Char]) -> IO [Char] -> Propellor [Char]
forall a b. (a -> b) -> a -> b
$ [Char] -> User -> IO [Char]
dotFile [Char]
"authorized_keys" User
user
		Propellor Bool
-> (Propellor Result, Propellor Result) -> Propellor Result
forall (m :: * -> *) a. Monad m => m Bool -> (m a, m a) -> m a
ifM (IO Bool -> Propellor Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Propellor Bool) -> IO Bool -> Propellor Bool
forall a b. (a -> b) -> a -> b
$ [Char] -> IO Bool
doesFileExist [Char]
f)
			( OuterMetaTypesWitness
  '[ 'Targeting 'OSDebian, 'Targeting 'OSBuntish,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
-> 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,
     'Targeting 'OSArchLinux, 'Targeting 'OSFreeBSD]
w (Property UnixLike -> Propellor Result)
-> Property UnixLike -> Propellor Result
forall a b. (a -> b) -> a -> b
$ [Char] -> User -> Property UnixLike -> Property UnixLike
modAuthorizedKey [Char]
f User
user (Property UnixLike -> Property UnixLike)
-> Property UnixLike -> Property UnixLike
forall a b. (a -> b) -> a -> b
$
				[Char]
f [Char] -> [Char] -> Property UnixLike
`File.lacksLine` [Char]
l
			, Result -> Propellor Result
forall (m :: * -> *) a. Monad m => a -> m a
return Result
NoChange
			)

modAuthorizedKey :: FilePath -> User -> Property UnixLike -> Property UnixLike
modAuthorizedKey :: [Char] -> User -> Property UnixLike -> Property UnixLike
modAuthorizedKey [Char]
f User
user Property UnixLike
p = Property UnixLike
p
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` [Char] -> FileMode -> Property UnixLike
File.mode [Char]
f ([FileMode] -> FileMode
combineModes [FileMode
ownerWriteMode, FileMode
ownerReadMode])
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` [Char] -> User -> Group -> Property UnixLike
File.ownerGroup [Char]
f User
user (User -> Group
userGroup User
user)
	Property UnixLike
-> Property UnixLike
-> CombinedType (Property UnixLike) (Property UnixLike)
forall x y. Combines x y => x -> y -> CombinedType x y
`before` [Char] -> User -> Group -> Property UnixLike
File.ownerGroup ([Char] -> [Char]
takeDirectory [Char]
f) User
user (User -> Group
userGroup User
user)