{-# LINE 1 "System/Posix/User.hsc" #-}
{-# LANGUAGE Trustworthy, CApiFFI, PatternSynonyms, ViewPatterns #-}
module System.Posix.User (
getRealUserID,
getRealGroupID,
getEffectiveUserID,
getEffectiveGroupID,
getGroups,
getLoginName,
getEffectiveUserName,
groupName,
groupPassword,
groupID,
groupMembers,
pattern GroupEntry,
getGroupEntryForID,
getGroupEntryForName,
getAllGroupEntries,
userName,
userPassword,
userID,
userGroupID,
userGecos,
homeDirectory,
userShell,
pattern UserEntry,
getUserEntryForID,
getUserEntryForName,
getAllUserEntries,
setUserID,
setGroupID,
setEffectiveUserID,
setEffectiveGroupID,
setGroups
) where
import System.Posix.Types
import System.IO.Unsafe (unsafePerformIO)
import Foreign.C
import Foreign.Ptr
import Foreign.Marshal
import Foreign.Storable
import System.Posix.User.Common ( UserEntry, GroupEntry
{-# LINE 70 "System/Posix/User.hsc" #-}
, unpackUserEntry, unpackGroupEntry, LKUPTYPE(..), CPasswd, CGroup
{-# LINE 72 "System/Posix/User.hsc" #-}
)
import qualified System.Posix.User.Common as User
{-# LINE 76 "System/Posix/User.hsc" #-}
{-# LINE 79 "System/Posix/User.hsc" #-}
import Control.Concurrent.MVar ( MVar, newMVar, withMVar )
import Control.Exception
{-# LINE 82 "System/Posix/User.hsc" #-}
import Control.Monad
import System.IO.Error
import qualified Data.ByteString.Char8 as C8
{-# LINE 90 "System/Posix/User.hsc" #-}
{-# LINE 155 "System/Posix/User.hsc" #-}
{-# LINE 221 "System/Posix/User.hsc" #-}
pwlock :: MVar ()
pwlock = unsafePerformIO $ newMVar ()
{-# NOINLINE pwlock #-}
lockpw :: LKUPTYPE -> IO a -> IO a
{-# LINE 234 "System/Posix/User.hsc" #-}
lockpw GETONE = id
lockpw GETALL = withMVar pwlock . const
{-# LINE 237 "System/Posix/User.hsc" #-}
{-# LINE 240 "System/Posix/User.hsc" #-}
{-# LINE 242 "System/Posix/User.hsc" #-}
grlock :: MVar ()
grlock = unsafePerformIO $ newMVar ()
{-# NOINLINE grlock #-}
lockgr :: LKUPTYPE -> IO a -> IO a
{-# LINE 255 "System/Posix/User.hsc" #-}
lockgr GETONE = id
lockgr GETALL = withMVar grlock . const
{-# LINE 258 "System/Posix/User.hsc" #-}
{-# LINE 261 "System/Posix/User.hsc" #-}
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)
{-# LINE 381 "System/Posix/User.hsc" #-}
groupName :: GroupEntry -> String
groupName (GroupEntry gn _ _ _) = gn
groupPassword :: GroupEntry -> String
groupPassword (GroupEntry _ gp _ _) = gp
groupID :: GroupEntry -> GroupID
groupID (GroupEntry _ _ id' _) = id'
groupMembers :: GroupEntry -> [String]
groupMembers (GroupEntry _ _ _ gm) = gm
pattern GroupEntry :: String
-> String
-> GroupID
-> [String]
-> GroupEntry
pattern GroupEntry gn gp gi gm <- User.GroupEntry (C8.unpack -> gn) (C8.unpack -> gp) gi (fmap C8.unpack -> gm) where
GroupEntry gn gp gi gm = User.GroupEntry (C8.pack gn) (C8.pack gp) gi (C8.pack <$> gm)
{-# COMPLETE GroupEntry #-}
{-# LINE 426 "System/Posix/User.hsc" #-}
getGroupEntryForID :: GroupID -> IO GroupEntry
{-# LINE 433 "System/Posix/User.hsc" #-}
getGroupEntryForID gid = lockgr GETONE $
allocaBytes (32) $ \pgr ->
{-# LINE 435 "System/Posix/User.hsc" #-}
doubleAllocWhileERANGE "getGroupEntryForID" "group"
grBufSize unpackGroupEntry $ c_getgrgid_r gid pgr
foreign import capi safe "HsUnix.h getgrgid_r"
c_getgrgid_r :: CGid -> Ptr CGroup -> CString
-> CSize -> Ptr (Ptr CGroup) -> IO CInt
{-# LINE 445 "System/Posix/User.hsc" #-}
getGroupEntryForName :: String -> IO GroupEntry
{-# LINE 452 "System/Posix/User.hsc" #-}
getGroupEntryForName name = lockgr GETONE $
allocaBytes (32) $ \pgr ->
{-# LINE 454 "System/Posix/User.hsc" #-}
withCAString name $ \ pstr ->
doubleAllocWhileERANGE "getGroupEntryForName" "group"
grBufSize unpackGroupEntry $ c_getgrnam_r pstr pgr
foreign import capi safe "HsUnix.h getgrnam_r"
c_getgrnam_r :: CString -> Ptr CGroup -> CString
-> CSize -> Ptr (Ptr CGroup) -> IO CInt
{-# LINE 465 "System/Posix/User.hsc" #-}
getAllGroupEntries :: IO [GroupEntry]
{-# LINE 476 "System/Posix/User.hsc" #-}
getAllGroupEntries = lockgr GETALL $ 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 safe "getgrent" c_getgrent :: IO (Ptr CGroup)
foreign import ccall safe "setgrent" c_setgrent :: IO ()
foreign import ccall safe "endgrent" c_endgrent :: IO ()
{-# LINE 493 "System/Posix/User.hsc" #-}
{-# LINE 495 "System/Posix/User.hsc" #-}
grBufSize :: Int
{-# LINE 497 "System/Posix/User.hsc" #-}
grBufSize = sysconfWithDefault 1024 (69)
{-# LINE 498 "System/Posix/User.hsc" #-}
{-# LINE 501 "System/Posix/User.hsc" #-}
{-# LINE 502 "System/Posix/User.hsc" #-}
{-# LINE 504 "System/Posix/User.hsc" #-}
userName :: UserEntry -> String
userName (UserEntry n _ _ _ _ _ _) = n
userPassword :: UserEntry -> String
userPassword (UserEntry _ p _ _ _ _ _) = p
userID :: UserEntry -> UserID
userID (UserEntry _ _ id' _ _ _ _) = id'
userGroupID :: UserEntry -> GroupID
userGroupID (UserEntry _ _ _ gid _ _ _) = gid
userGecos :: UserEntry -> String
userGecos (UserEntry _ _ _ _ ge _ _) = ge
homeDirectory :: UserEntry -> String
homeDirectory (UserEntry _ _ _ _ _ hd _) = hd
userShell :: UserEntry -> String
userShell (UserEntry _ _ _ _ _ _ us) = us
pattern UserEntry :: String
-> String
-> UserID
-> GroupID
-> String
-> String
-> String
-> UserEntry
pattern UserEntry un up ui ugi ug hd us <- User.UserEntry (C8.unpack -> un)
(C8.unpack -> up)
ui
ugi
(C8.unpack -> ug)
(C8.unpack -> hd)
(C8.unpack -> us) where
UserEntry un up ui ugi ug hd us = User.UserEntry (C8.pack un)
(C8.pack up)
ui
ugi
(C8.pack ug)
(C8.pack hd)
(C8.pack us)
{-# COMPLETE UserEntry #-}
getUserEntryForID :: UserID -> IO UserEntry
{-# LINE 561 "System/Posix/User.hsc" #-}
getUserEntryForID uid = lockpw GETONE $
allocaBytes (48) $ \ppw ->
{-# LINE 563 "System/Posix/User.hsc" #-}
doubleAllocWhileERANGE "getUserEntryForID" "user"
pwBufSize unpackUserEntry $ c_getpwuid_r uid ppw
foreign import capi safe "HsUnix.h getpwuid_r"
c_getpwuid_r :: CUid -> Ptr CPasswd ->
CString -> CSize -> Ptr (Ptr CPasswd) -> IO CInt
{-# LINE 573 "System/Posix/User.hsc" #-}
getUserEntryForName :: String -> IO UserEntry
{-# LINE 580 "System/Posix/User.hsc" #-}
getUserEntryForName name = lockpw GETONE $
allocaBytes (48) $ \ppw ->
{-# LINE 582 "System/Posix/User.hsc" #-}
withCAString name $ \ pstr ->
doubleAllocWhileERANGE "getUserEntryForName" "user"
pwBufSize unpackUserEntry $ c_getpwnam_r pstr ppw
foreign import capi safe "HsUnix.h getpwnam_r"
c_getpwnam_r :: CString -> Ptr CPasswd
-> CString -> CSize -> Ptr (Ptr CPasswd) -> IO CInt
{-# LINE 593 "System/Posix/User.hsc" #-}
getAllUserEntries :: IO [UserEntry]
{-# LINE 598 "System/Posix/User.hsc" #-}
getAllUserEntries = lockpw GETALL $ 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 safe "getpwent" c_getpwent :: IO (Ptr CPasswd)
foreign import ccall safe "setpwent" c_setpwent :: IO ()
foreign import ccall safe "endpwent" c_endpwent :: IO ()
{-# LINE 615 "System/Posix/User.hsc" #-}
{-# LINE 617 "System/Posix/User.hsc" #-}
pwBufSize :: Int
{-# LINE 619 "System/Posix/User.hsc" #-}
pwBufSize = sysconfWithDefault 1024 (70)
{-# LINE 620 "System/Posix/User.hsc" #-}
{-# LINE 623 "System/Posix/User.hsc" #-}
{-# LINE 624 "System/Posix/User.hsc" #-}
{-# LINE 626 "System/Posix/User.hsc" #-}
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
{-# LINE 638 "System/Posix/User.hsc" #-}
{-# LINE 640 "System/Posix/User.hsc" #-}
doubleAllocWhileERANGE
:: String
-> String
-> Int
-> (Ptr r -> IO a)
-> (Ptr b -> CSize -> Ptr (Ptr r) -> IO CInt)
-> IO a
doubleAllocWhileERANGE loc enttype initlen unpack action =
alloca $ go initlen
where
go len res = do
r <- allocaBytes len $ \buf -> do
rc <- action buf (fromIntegral len) res
if rc /= 0
then return (Left rc)
else do p <- peek res
when (p == nullPtr) $ notFoundErr
fmap Right (unpack p)
case r of
Right x -> return x
Left rc | Errno rc == eRANGE ->
go (2 * len) res
Left rc ->
ioError (errnoToIOError loc (Errno rc) Nothing Nothing)
notFoundErr =
ioError $ flip ioeSetErrorString ("no such " ++ enttype)
$ mkIOError doesNotExistErrorType loc 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
{-# LINE 689 "System/Posix/User.hsc" #-}