summaryrefslogtreecommitdiff
path: root/src/Propellor/Property/Kerberos.hs
diff options
context:
space:
mode:
authorJelmer Vernooij2015-09-27 23:24:54 +0000
committerJoey Hess2015-09-29 10:39:27 -0400
commitb13b3c5010f0b1d3bc0d57f2c182cfef7a0b5962 (patch)
tree16db9e9a515862754826327602d01e5d366868c2 /src/Propellor/Property/Kerberos.hs
parentd9bfd1eb50b8ac3f7621be238eb69833a6e4539a (diff)
Add basic Kerberos module.
Diffstat (limited to 'src/Propellor/Property/Kerberos.hs')
-rw-r--r--src/Propellor/Property/Kerberos.hs94
1 files changed, 94 insertions, 0 deletions
diff --git a/src/Propellor/Property/Kerberos.hs b/src/Propellor/Property/Kerberos.hs
new file mode 100644
index 00000000..74388423
--- /dev/null
+++ b/src/Propellor/Property/Kerberos.hs
@@ -0,0 +1,94 @@
+module Propellor.Property.Kerberos where
+
+import Data.String.Utils
+import Utility.FileSystemEncoding
+import Utility.Process
+
+import Propellor
+import qualified Propellor.Property.Apt as Apt
+import qualified Propellor.Property.File as File
+import Propellor.Property.User
+
+type Realm = String
+type Principal = String
+type Kvno = Integer
+
+-- Standard paths in MIT Kerberos
+
+defaultKeyTab :: FilePath
+defaultKeyTab = "/etc/krb5.keytab"
+
+kadmAclPath :: FilePath
+kadmAclPath = "/etc/krb5kdc/kadm5.acl"
+
+kpropdAclPath :: FilePath
+kpropdAclPath = "/etc/krb5kdc/kpropd.acl"
+
+kdcConfPath :: FilePath
+kdcConfPath = "/etc/krb5kdc/kdc.conf"
+
+keyTabPath :: Maybe FilePath -> FilePath
+keyTabPath = maybe defaultKeyTab id
+
+-- Create a principal from a primary, instance and realm
+principal :: String -> Maybe String -> Maybe Realm -> Principal
+principal p i r = p ++ maybe "" ("/"++) i ++ maybe "" ("@" ++) r
+
+installed :: Property NoInfo
+installed = Apt.installed ["krb5-user"]
+
+kdcInstalled :: Property NoInfo
+kdcInstalled = Apt.serviceInstalledRunning "krb5-kdc"
+
+adminServerInstalled :: Property NoInfo
+adminServerInstalled = Apt.serviceInstalledRunning "krb5-admin-server"
+
+kpropServerInstalled :: Property HasInfo
+kpropServerInstalled = propertyList "kprop server installed" $ props
+ & kdcInstalled
+ & Apt.installed ["openbsd-inetd"]
+ & "/etc/inetd.conf" `File.containsLines`
+ [ "krb5_prop\tstream\ttcp\tnowait\troot\t/usr/sbin/kpropd kpropd"
+ , "krb5_prop\tstream\ttcp6\tnowait\troot\t/usr/sbin/kpropd kpropd"
+ ]
+
+kpropAcls :: [String] -> Property NoInfo
+kpropAcls ps = kpropdAclPath `File.hasContent` ps `describe` "kprop server ACLs"
+
+k5srvutil :: (Maybe FilePath) -> [String] -> IO String
+k5srvutil kt cmd = readProcess "k5srvutil" (maybe [] (\x -> ["-f", x]) kt ++ cmd)
+
+-- Keytab management
+keytabEntries :: Maybe FilePath -> IO [(Kvno, Principal)]
+keytabEntries p = do
+ c <- k5srvutil p ["list"]
+ return $ map parseLine (drop 3 $ lines c)
+ where
+ parseLine l = (Prelude.read x, y) where (x, y) = splitAt 5 l
+
+checkKeyTabEntry' :: Maybe FilePath -> (Kvno, Principal) -> IO Bool
+checkKeyTabEntry' path entry = do
+ entries <- keytabEntries path
+ return $ entry `elem` entries
+
+checkKeyTabEntry :: Maybe FilePath -> Principal -> IO Bool
+checkKeyTabEntry path princ = do
+ entries <- keytabEntries path
+ return $ princ `elem` (map snd entries)
+
+-- k5login files
+k5loginPath :: User -> IO FilePath
+k5loginPath user = do
+ h <- homedir user
+ return $ h </> ".k5login"
+
+k5login :: User -> [Principal] -> Property NoInfo
+k5login user@(User u) ps = property (u ++ " has k5login") $ do
+ f <- liftIO $ k5loginPath user
+ liftIO $ do
+ createDirectoryIfMissing True (takeDirectory f)
+ writeFile f (unlines ps)
+ ensureProperties
+ [ File.ownerGroup f user (userGroup user)
+ , File.ownerGroup (takeDirectory f) user (userGroup user)
+ ]