propellor/src/Propellor/Property/User.hs

87 lines
2.8 KiB
Haskell
Raw Normal View History

2014-03-31 03:37:54 +00:00
module Propellor.Property.User where
import System.Posix
2014-03-31 03:55:59 +00:00
import Propellor
2014-03-30 20:53:31 +00:00
data Eep = YesReallyDeleteHome
2014-04-01 20:58:11 +00:00
accountFor :: UserName -> Property
2014-04-13 06:28:40 +00:00
accountFor user = check (isNothing <$> catchMaybeIO (homedir user)) $ cmdProperty "adduser"
2014-03-31 03:55:59 +00:00
[ "--disabled-password"
, "--gecos", ""
, user
]
2014-04-01 21:03:03 +00:00
`describe` ("account for " ++ user)
2014-04-01 20:58:11 +00:00
-- | Removes user home directory!! Use with caution.
2014-03-30 20:53:31 +00:00
nuked :: UserName -> Eep -> Property
2014-04-13 06:28:40 +00:00
nuked user _ = check (isJust <$> catchMaybeIO (homedir user)) $ cmdProperty "userdel"
2014-03-31 03:55:59 +00:00
[ "-r"
, user
2014-03-30 04:17:44 +00:00
]
2014-03-30 19:53:35 +00:00
`describe` ("nuked user " ++ user)
2014-03-30 04:17:44 +00:00
2014-04-01 20:58:11 +00:00
-- | Only ensures that the user has some password set. It may or may
-- not be the password from the PrivData.
hasSomePassword :: UserName -> Property
hasSomePassword user = property (user ++ "has password") $ do
hostname <- asks hostName
ensureProperty $ hasSomePassword' user (Context hostname)
2014-07-06 19:56:56 +00:00
-- | While hasSomePassword uses the name of the host as context,
-- this allows specifying a different context. This is useful when
-- you want to use the same password on multiple hosts, for example.
hasSomePassword' :: UserName -> Context -> Property
hasSomePassword' user context = check ((/= HasPassword) <$> getPasswordStatus user) $
hasPassword' user context
-- | Ensures that a user's password is set to the password from the PrivData.
-- (Will change any existing password.)
hasPassword :: UserName -> Property
hasPassword user = property (user ++ "has password") $ do
hostname <- asks hostName
ensureProperty $ hasPassword' user (Context hostname)
hasPassword' :: UserName -> Context -> Property
hasPassword' user context = withPrivData (Password user) context $ \getpassword ->
property (user ++ " has password") $
2014-07-06 19:56:56 +00:00
getpassword $ \password -> makeChange $
withHandle StdinHandle createProcessSuccess
(proc "chpasswd" []) $ \h -> do
hPutStrLn h $ user ++ ":" ++ password
hClose h
2014-03-30 23:10:32 +00:00
2014-03-30 04:17:44 +00:00
lockedPassword :: UserName -> Property
lockedPassword user = check (not <$> isLockedPassword user) $ cmdProperty "passwd"
2014-03-31 03:55:59 +00:00
[ "--lock"
, user
2014-03-30 04:17:44 +00:00
]
2014-03-30 19:53:35 +00:00
`describe` ("locked " ++ user ++ " password")
2014-03-30 04:17:44 +00:00
2014-03-31 00:18:45 +00:00
data PasswordStatus = NoPassword | LockedPassword | HasPassword
deriving (Eq)
getPasswordStatus :: UserName -> IO PasswordStatus
getPasswordStatus user = parse . words <$> readProcess "passwd" ["-S", user]
where
2014-03-31 00:18:45 +00:00
parse (_:"L":_) = LockedPassword
parse (_:"NP":_) = NoPassword
parse (_:"P":_) = HasPassword
parse _ = NoPassword
isLockedPassword :: UserName -> IO Bool
isLockedPassword user = (== LockedPassword) <$> getPasswordStatus user
2014-04-13 06:28:40 +00:00
homedir :: UserName -> IO FilePath
homedir user = homeDirectory <$> getUserEntryForName user
hasGroup :: UserName -> GroupName -> Property
hasGroup user group' = check test $ cmdProperty "adduser"
[ user
, group'
]
`describe` unwords ["user", user, "in group", group']
where
2014-11-23 18:37:37 +00:00
test = not . elem group' . words <$> readProcess "groups" [user]