{-# LINE 1 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LANGUAGE Trustworthy, CApiFFI, PatternSynonyms, ViewPatterns #-}
module System.Posix.User.ByteString (
    
    
    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 System.IO.Unsafe (unsafePerformIO)
import Foreign.C ( CSize(..), CInt(..), CString, CLong(..), getErrno, throwErrno, eOK, throwErrnoIfMinus1_, throwErrnoIfNull, resetErrno, Errno(..), eRANGE, errnoToIOError )
import Foreign.Ptr
import Foreign.Marshal
import Foreign.Storable
import System.Posix.User.Common
{-# LINE 61 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 64 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
import Control.Concurrent.MVar ( MVar, newMVar, withMVar )
import Control.Exception
{-# LINE 67 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
import Control.Monad
import System.IO.Error
import Data.ByteString ( ByteString, packCString, useAsCString )
{-# LINE 75 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 140 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 206 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
pwlock :: MVar ()
pwlock :: MVar ()
pwlock = IO (MVar ()) -> MVar ()
forall a. IO a -> a
unsafePerformIO (IO (MVar ()) -> MVar ()) -> IO (MVar ()) -> MVar ()
forall a b. (a -> b) -> a -> b
$ () -> IO (MVar ())
forall a. a -> IO (MVar a)
newMVar ()
{-# NOINLINE pwlock #-}
lockpw :: LKUPTYPE -> IO a -> IO a
{-# LINE 219 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
lockpw :: forall a. LKUPTYPE -> IO a -> IO a
lockpw LKUPTYPE
GETONE = IO a -> IO a
forall a. a -> a
id
lockpw LKUPTYPE
GETALL = MVar () -> (() -> IO a) -> IO a
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar ()
pwlock ((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const
{-# LINE 222 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 225 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 227 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
grlock :: MVar ()
grlock :: MVar ()
grlock = IO (MVar ()) -> MVar ()
forall a. IO a -> a
unsafePerformIO (IO (MVar ()) -> MVar ()) -> IO (MVar ()) -> MVar ()
forall a b. (a -> b) -> a -> b
$ () -> IO (MVar ())
forall a. a -> IO (MVar a)
newMVar ()
{-# NOINLINE grlock #-}
lockgr :: LKUPTYPE -> IO a -> IO a
{-# LINE 240 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
lockgr :: forall a. LKUPTYPE -> IO a -> IO a
lockgr LKUPTYPE
GETONE = IO a -> IO a
forall a. a -> a
id
lockgr LKUPTYPE
GETALL = MVar () -> (() -> IO a) -> IO a
forall a b. MVar a -> (a -> IO b) -> IO b
withMVar MVar ()
grlock ((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const
{-# LINE 243 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 246 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getRealUserID :: IO UserID
getRealUserID :: IO UserID
getRealUserID = IO UserID
c_getuid
foreign import ccall unsafe "getuid"
  c_getuid :: IO CUid
getRealGroupID :: IO GroupID
getRealGroupID :: IO GroupID
getRealGroupID = IO GroupID
c_getgid
foreign import ccall unsafe "getgid"
  c_getgid :: IO CGid
getEffectiveUserID :: IO UserID
getEffectiveUserID :: IO UserID
getEffectiveUserID = IO UserID
c_geteuid
foreign import ccall unsafe "geteuid"
  c_geteuid :: IO CUid
getEffectiveGroupID :: IO GroupID
getEffectiveGroupID :: IO GroupID
getEffectiveGroupID = IO GroupID
c_getegid
foreign import ccall unsafe "getegid"
  c_getegid :: IO CGid
getGroups :: IO [GroupID]
getGroups :: IO [GroupID]
getGroups = do
    CInt
ngroups <- CInt -> Ptr GroupID -> IO CInt
c_getgroups CInt
0 Ptr GroupID
forall a. Ptr a
nullPtr
    Int -> (Ptr GroupID -> IO [GroupID]) -> IO [GroupID]
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
ngroups) ((Ptr GroupID -> IO [GroupID]) -> IO [GroupID])
-> (Ptr GroupID -> IO [GroupID]) -> IO [GroupID]
forall a b. (a -> b) -> a -> b
$ \Ptr GroupID
arr -> do
       String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"getGroups" (CInt -> Ptr GroupID -> IO CInt
c_getgroups CInt
ngroups Ptr GroupID
arr)
       [GroupID]
groups <- Int -> Ptr GroupID -> IO [GroupID]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
ngroups) Ptr GroupID
arr
       [GroupID] -> IO [GroupID]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [GroupID]
groups
foreign import ccall unsafe "getgroups"
  c_getgroups :: CInt -> Ptr CGid -> IO CInt
setGroups :: [GroupID] -> IO ()
setGroups :: [GroupID] -> IO ()
setGroups [GroupID]
groups = do
    [GroupID] -> (Int -> Ptr GroupID -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [GroupID]
groups ((Int -> Ptr GroupID -> IO ()) -> IO ())
-> (Int -> Ptr GroupID -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Int
ngroups Ptr GroupID
arr ->
       String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"setGroups" (CInt -> Ptr GroupID -> IO CInt
c_setgroups (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ngroups) Ptr GroupID
arr)
foreign import ccall unsafe "setgroups"
  c_setgroups :: CInt -> Ptr CGid -> IO CInt
getLoginName :: IO ByteString
getLoginName :: IO ByteString
getLoginName =  do
    
    Ptr CChar
str <- String -> IO (Ptr CChar) -> IO (Ptr CChar)
forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwErrnoIfNull String
"getLoginName" IO (Ptr CChar)
c_getlogin
    Ptr CChar -> IO ByteString
packCString Ptr CChar
str
foreign import ccall unsafe "getlogin"
  c_getlogin :: IO CString
setUserID :: UserID -> IO ()
setUserID :: UserID -> IO ()
setUserID UserID
uid = String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"setUserID" (UserID -> IO CInt
c_setuid UserID
uid)
foreign import ccall unsafe "setuid"
  c_setuid :: CUid -> IO CInt
setEffectiveUserID :: UserID -> IO ()
setEffectiveUserID :: UserID -> IO ()
setEffectiveUserID UserID
uid = String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"setEffectiveUserID" (UserID -> IO CInt
c_seteuid UserID
uid)
foreign import ccall unsafe "seteuid"
  c_seteuid :: CUid -> IO CInt
setGroupID :: GroupID -> IO ()
setGroupID :: GroupID -> IO ()
setGroupID GroupID
gid = String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"setGroupID" (GroupID -> IO CInt
c_setgid GroupID
gid)
foreign import ccall unsafe "setgid"
  c_setgid :: CGid -> IO CInt
setEffectiveGroupID :: GroupID -> IO ()
setEffectiveGroupID :: GroupID -> IO ()
setEffectiveGroupID GroupID
gid =
  String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ String
"setEffectiveGroupID" (GroupID -> IO CInt
c_setegid GroupID
gid)
foreign import ccall unsafe "setegid"
  c_setegid :: CGid -> IO CInt
getEffectiveUserName :: IO ByteString
getEffectiveUserName :: IO ByteString
getEffectiveUserName = do
    UserID
euid <- IO UserID
getEffectiveUserID
    UserEntry
pw <- UserID -> IO UserEntry
getUserEntryForID UserID
euid
    ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (UserEntry -> ByteString
userName UserEntry
pw)
{-# LINE 366 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 389 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getGroupEntryForID :: GroupID -> IO GroupEntry
{-# LINE 396 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getGroupEntryForID gid = lockgr GETONE $
    allocaBytes (32) $ \pgr ->
{-# LINE 398 "libraries/unix/System/Posix/User/ByteString.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 408 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getGroupEntryForName :: ByteString -> IO GroupEntry
{-# LINE 415 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getGroupEntryForName name = lockgr GETONE $
    allocaBytes (32) $ \pgr ->
{-# LINE 417 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
        useAsCString 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 428 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getAllGroupEntries :: IO [GroupEntry]
{-# LINE 439 "libraries/unix/System/Posix/User/ByteString.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 456 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 458 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
grBufSize :: Int
{-# LINE 460 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
grBufSize = sysconfWithDefault 1024 (69)
{-# LINE 461 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 464 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 465 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 467 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getUserEntryForID :: UserID -> IO UserEntry
{-# LINE 478 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getUserEntryForID uid = lockpw GETONE $
    allocaBytes (48) $ \ppw ->
{-# LINE 480 "libraries/unix/System/Posix/User/ByteString.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 490 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getUserEntryForName :: ByteString -> IO UserEntry
{-# LINE 497 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getUserEntryForName name = lockpw GETONE $
    allocaBytes (48) $ \ppw ->
{-# LINE 499 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
        useAsCString 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 510 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
getAllUserEntries :: IO [UserEntry]
{-# LINE 515 "libraries/unix/System/Posix/User/ByteString.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 532 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 534 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
pwBufSize :: Int
{-# LINE 536 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
pwBufSize = sysconfWithDefault 1024 (70)
{-# LINE 537 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 540 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 541 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 543 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
foreign import ccall unsafe "sysconf"
  c_sysconf :: CInt -> IO CLong
sysconfWithDefault :: Int -> CInt -> Int
sysconfWithDefault :: Int -> CInt -> Int
sysconfWithDefault Int
def CInt
sc =
    IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ do Int
v <- (CLong -> Int) -> IO CLong -> IO Int
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CLong -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO CLong -> IO Int) -> IO CLong -> IO Int
forall a b. (a -> b) -> a -> b
$ CInt -> IO CLong
c_sysconf CInt
sc
                         Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$ if Int
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (-Int
1) then Int
def else Int
v
{-# LINE 555 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
{-# LINE 557 "libraries/unix/System/Posix/User/ByteString.hsc" #-}
doubleAllocWhileERANGE
  :: String
  -> String 
  -> Int
  -> (Ptr r -> IO a)
  -> (Ptr b -> CSize -> Ptr (Ptr r) -> IO CInt)
  -> IO a
doubleAllocWhileERANGE :: forall r a b.
String
-> String
-> Int
-> (Ptr r -> IO a)
-> (Ptr b -> CSize -> Ptr (Ptr r) -> IO CInt)
-> IO a
doubleAllocWhileERANGE String
loc String
enttype Int
initlen Ptr r -> IO a
unpack Ptr b -> CSize -> Ptr (Ptr r) -> IO CInt
action =
  (Ptr (Ptr r) -> IO a) -> IO a
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr (Ptr r) -> IO a) -> IO a) -> (Ptr (Ptr r) -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ Int -> Ptr (Ptr r) -> IO a
go Int
initlen
 where
  go :: Int -> Ptr (Ptr r) -> IO a
go Int
len Ptr (Ptr r)
res = do
    Either CInt a
r <- Int -> (Ptr b -> IO (Either CInt a)) -> IO (Either CInt a)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
len ((Ptr b -> IO (Either CInt a)) -> IO (Either CInt a))
-> (Ptr b -> IO (Either CInt a)) -> IO (Either CInt a)
forall a b. (a -> b) -> a -> b
$ \Ptr b
buf -> do
           CInt
rc <- Ptr b -> CSize -> Ptr (Ptr r) -> IO CInt
action Ptr b
buf (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) Ptr (Ptr r)
res
           if CInt
rc CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0
             then Either CInt a -> IO (Either CInt a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CInt -> Either CInt a
forall a b. a -> Either a b
Left CInt
rc)
             else do Ptr r
p <- Ptr (Ptr r) -> IO (Ptr r)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr r)
res
                     Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Ptr r
p Ptr r -> Ptr r -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr r
forall a. Ptr a
nullPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO ()
forall {a}. IO a
notFoundErr
                     (a -> Either CInt a) -> IO a -> IO (Either CInt a)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Either CInt a
forall a b. b -> Either a b
Right (Ptr r -> IO a
unpack Ptr r
p)
    case Either CInt a
r of
      Right a
x -> a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
      Left CInt
rc | CInt -> Errno
Errno CInt
rc Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
eRANGE ->
        
        
        Int -> Ptr (Ptr r) -> IO a
go (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
len) Ptr (Ptr r)
res
      Left CInt
rc ->
        IOError -> IO a
forall a. IOError -> IO a
ioError (String -> Errno -> Maybe Handle -> Maybe String -> IOError
errnoToIOError String
loc (CInt -> Errno
Errno CInt
rc) Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing)
  notFoundErr :: IO a
notFoundErr =
    IOError -> IO a
forall a. IOError -> IO a
ioError (IOError -> IO a) -> IOError -> IO a
forall a b. (a -> b) -> a -> b
$ (IOError -> String -> IOError) -> String -> IOError -> IOError
forall a b c. (a -> b -> c) -> b -> a -> c
flip IOError -> String -> IOError
ioeSetErrorString (String
"no such " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
enttype)
            (IOError -> IOError) -> IOError -> IOError
forall a b. (a -> b) -> a -> b
$ IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
doesNotExistErrorType String
loc Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
throwErrnoIfNullAndError :: String -> IO (Ptr a) -> IO (Ptr a)
throwErrnoIfNullAndError :: forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwErrnoIfNullAndError String
loc IO (Ptr a)
act = do
    Ptr a
rc <- IO (Ptr a)
act
    Errno
errno <- IO Errno
getErrno
    if Ptr a
rc Ptr a -> Ptr a -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr a
forall a. Ptr a
nullPtr Bool -> Bool -> Bool
&& Errno
errno Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
/= Errno
eOK
       then String -> IO (Ptr a)
forall a. String -> IO a
throwErrno String
loc
       else Ptr a -> IO (Ptr a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr a
rc
{-# LINE 605 "libraries/unix/System/Posix/User/ByteString.hsc" #-}