module System.Posix.User (
getRealUserID,
getRealGroupID,
getEffectiveUserID,
getEffectiveGroupID,
getGroups,
getLoginName,
getEffectiveUserName,
GroupEntry(..),
getGroupEntryForID,
getGroupEntryForName,
getAllGroupEntries,
UserEntry(..),
getUserEntryForID,
getUserEntryForName,
getAllUserEntries,
setUserID,
setGroupID,
setEffectiveUserID,
setEffectiveGroupID,
setGroups
) where
import System.Posix.Types
import Foreign hiding (unsafePerformIO)
import System.IO.Unsafe (unsafePerformIO)
import Foreign.C
import System.Posix.Internals ( CGroup, CPasswd )
import Control.Concurrent.MVar ( MVar, newMVar, withMVar )
import Control.Exception
import Control.Monad
import System.IO.Error
getRealUserID :: IO UserID
getRealUserID = c_getuid
foreign import ccall unsafe "getuid"
c_getuid :: IO CUid
getRealGroupID :: IO GroupID
getRealGroupID = c_getgid
foreign import ccall unsafe "getgid"
c_getgid :: IO CGid
getEffectiveUserID :: IO UserID
getEffectiveUserID = c_geteuid
foreign import ccall unsafe "geteuid"
c_geteuid :: IO CUid
getEffectiveGroupID :: IO GroupID
getEffectiveGroupID = c_getegid
foreign import ccall unsafe "getegid"
c_getegid :: IO CGid
getGroups :: IO [GroupID]
getGroups = do
ngroups <- c_getgroups 0 nullPtr
allocaArray (fromIntegral ngroups) $ \arr -> do
throwErrnoIfMinus1_ "getGroups" (c_getgroups ngroups arr)
groups <- peekArray (fromIntegral ngroups) arr
return groups
foreign import ccall unsafe "getgroups"
c_getgroups :: CInt -> Ptr CGid -> IO CInt
setGroups :: [GroupID] -> IO ()
setGroups groups = do
withArrayLen groups $ \ ngroups arr ->
throwErrnoIfMinus1_ "setGroups" (c_setgroups (fromIntegral ngroups) arr)
foreign import ccall unsafe "setgroups"
c_setgroups :: CInt -> Ptr CGid -> IO CInt
getLoginName :: IO String
getLoginName = do
str <- throwErrnoIfNull "getLoginName" c_getlogin
peekCAString str
foreign import ccall unsafe "getlogin"
c_getlogin :: IO CString
setUserID :: UserID -> IO ()
setUserID uid = throwErrnoIfMinus1_ "setUserID" (c_setuid uid)
foreign import ccall unsafe "setuid"
c_setuid :: CUid -> IO CInt
setEffectiveUserID :: UserID -> IO ()
setEffectiveUserID uid = throwErrnoIfMinus1_ "setEffectiveUserID" (c_seteuid uid)
foreign import ccall unsafe "seteuid"
c_seteuid :: CUid -> IO CInt
setGroupID :: GroupID -> IO ()
setGroupID gid = throwErrnoIfMinus1_ "setGroupID" (c_setgid gid)
foreign import ccall unsafe "setgid"
c_setgid :: CGid -> IO CInt
setEffectiveGroupID :: GroupID -> IO ()
setEffectiveGroupID gid =
throwErrnoIfMinus1_ "setEffectiveGroupID" (c_setegid gid)
foreign import ccall unsafe "setegid"
c_setegid :: CGid -> IO CInt
getEffectiveUserName :: IO String
getEffectiveUserName = do
euid <- getEffectiveUserID
pw <- getUserEntryForID euid
return (userName pw)
data GroupEntry =
GroupEntry {
groupName :: String,
groupPassword :: String,
groupID :: GroupID,
groupMembers :: [String]
} deriving (Show, Read, Eq)
getGroupEntryForID :: GroupID -> IO GroupEntry
getGroupEntryForID gid = do
allocaBytes (16) $ \pgr ->
alloca $ \ ppgr -> do
throwErrorIfNonZero_ "getGroupEntryForID" $
doubleAllocWhile isERANGE grBufSize $ \s b ->
c_getgrgid_r gid pgr b (fromIntegral s) ppgr
_ <- throwErrnoIfNull "getGroupEntryForID" $
peekElemOff ppgr 0
unpackGroupEntry pgr
foreign import ccall unsafe "getgrgid_r"
c_getgrgid_r :: CGid -> Ptr CGroup -> CString
-> CSize -> Ptr (Ptr CGroup) -> IO CInt
getGroupEntryForName :: String -> IO GroupEntry
getGroupEntryForName name = do
allocaBytes (16) $ \pgr ->
alloca $ \ ppgr ->
withCAString name $ \ pstr -> do
throwErrorIfNonZero_ "getGroupEntryForName" $
doubleAllocWhile isERANGE grBufSize $ \s b ->
c_getgrnam_r pstr pgr b (fromIntegral s) ppgr
r <- peekElemOff ppgr 0
when (r == nullPtr) $
ioError $ flip ioeSetErrorString "no group name"
$ mkIOError doesNotExistErrorType
"getGroupEntryForName"
Nothing
(Just name)
unpackGroupEntry pgr
foreign import ccall unsafe "getgrnam_r"
c_getgrnam_r :: CString -> Ptr CGroup -> CString
-> CSize -> Ptr (Ptr CGroup) -> IO CInt
getAllGroupEntries :: IO [GroupEntry]
getAllGroupEntries =
withMVar lock $ \_ -> bracket_ c_setgrent c_endgrent $ worker []
where worker accum =
do resetErrno
ppw <- throwErrnoIfNullAndError "getAllGroupEntries" $
c_getgrent
if ppw == nullPtr
then return (reverse accum)
else do thisentry <- unpackGroupEntry ppw
worker (thisentry : accum)
foreign import ccall unsafe "getgrent"
c_getgrent :: IO (Ptr CGroup)
foreign import ccall unsafe "setgrent"
c_setgrent :: IO ()
foreign import ccall unsafe "endgrent"
c_endgrent :: IO ()
grBufSize :: Int
grBufSize = sysconfWithDefault 1024 (69)
unpackGroupEntry :: Ptr CGroup -> IO GroupEntry
unpackGroupEntry ptr = do
name <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) ptr >>= peekCAString
passwd <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) ptr >>= peekCAString
gid <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) ptr
mem <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) ptr
members <- peekArray0 nullPtr mem >>= mapM peekCAString
return (GroupEntry name passwd gid members)
data UserEntry =
UserEntry {
userName :: String,
userPassword :: String,
userID :: UserID,
userGroupID :: GroupID,
userGecos :: String,
homeDirectory :: String,
userShell :: String
} deriving (Show, Read, Eq)
lock :: MVar ()
lock = unsafePerformIO $ newMVar ()
getUserEntryForID :: UserID -> IO UserEntry
getUserEntryForID uid = do
allocaBytes (28) $ \ppw ->
alloca $ \ pppw -> do
throwErrorIfNonZero_ "getUserEntryForID" $
doubleAllocWhile isERANGE pwBufSize $ \s b ->
c_getpwuid_r uid ppw b (fromIntegral s) pppw
_ <- throwErrnoIfNull "getUserEntryForID" $
peekElemOff pppw 0
unpackUserEntry ppw
foreign import ccall unsafe "__hsunix_getpwuid_r"
c_getpwuid_r :: CUid -> Ptr CPasswd ->
CString -> CSize -> Ptr (Ptr CPasswd) -> IO CInt
getUserEntryForName :: String -> IO UserEntry
getUserEntryForName name = do
allocaBytes (28) $ \ppw ->
alloca $ \ pppw ->
withCAString name $ \ pstr -> do
throwErrorIfNonZero_ "getUserEntryForName" $
doubleAllocWhile isERANGE pwBufSize $ \s b ->
c_getpwnam_r pstr ppw b (fromIntegral s) pppw
r <- peekElemOff pppw 0
when (r == nullPtr) $
ioError $ flip ioeSetErrorString "no user name"
$ mkIOError doesNotExistErrorType
"getUserEntryForName"
Nothing
(Just name)
unpackUserEntry ppw
foreign import ccall unsafe "__hsunix_getpwnam_r"
c_getpwnam_r :: CString -> Ptr CPasswd
-> CString -> CSize -> Ptr (Ptr CPasswd) -> IO CInt
getAllUserEntries :: IO [UserEntry]
getAllUserEntries =
withMVar lock $ \_ -> bracket_ c_setpwent c_endpwent $ worker []
where worker accum =
do resetErrno
ppw <- throwErrnoIfNullAndError "getAllUserEntries" $
c_getpwent
if ppw == nullPtr
then return (reverse accum)
else do thisentry <- unpackUserEntry ppw
worker (thisentry : accum)
foreign import ccall unsafe "__hsunix_getpwent"
c_getpwent :: IO (Ptr CPasswd)
foreign import ccall unsafe "setpwent"
c_setpwent :: IO ()
foreign import ccall unsafe "endpwent"
c_endpwent :: IO ()
pwBufSize :: Int
pwBufSize = sysconfWithDefault 1024 (70)
foreign import ccall unsafe "sysconf"
c_sysconf :: CInt -> IO CLong
sysconfWithDefault :: Int -> CInt -> Int
sysconfWithDefault def sc =
unsafePerformIO $ do v <- fmap fromIntegral $ c_sysconf sc
return $ if v == (1) then def else v
isERANGE :: Integral a => a -> Bool
isERANGE = (== eRANGE) . Errno . fromIntegral
doubleAllocWhile :: (a -> Bool) -> Int -> (Int -> Ptr b -> IO a) -> IO a
doubleAllocWhile p s m = do
r <- allocaBytes s (m s)
if p r then doubleAllocWhile p (2 * s) m else return r
unpackUserEntry :: Ptr CPasswd -> IO UserEntry
unpackUserEntry ptr = do
name <- ((\hsc_ptr -> peekByteOff hsc_ptr 0)) ptr >>= peekCAString
passwd <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) ptr >>= peekCAString
uid <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) ptr
gid <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) ptr
gecos <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) ptr >>= peekCAString
dir <- ((\hsc_ptr -> peekByteOff hsc_ptr 20)) ptr >>= peekCAString
shell <- ((\hsc_ptr -> peekByteOff hsc_ptr 24)) ptr >>= peekCAString
return (UserEntry name passwd uid gid gecos dir shell)
throwErrorIfNonZero_ :: String -> IO CInt -> IO ()
throwErrorIfNonZero_ loc act = do
rc <- act
if (rc == 0)
then return ()
else ioError (errnoToIOError loc (Errno rc) Nothing Nothing)
throwErrnoIfNullAndError :: String -> IO (Ptr a) -> IO (Ptr a)
throwErrnoIfNullAndError loc act = do
rc <- act
errno <- getErrno
if rc == nullPtr && errno /= eOK
then throwErrno loc
else return rc