{-# LINE 1 "System/Posix/User/Common.hsc" #-}{-# LANGUAGE Safe #-}------------------------------------------------------------------------------- |-- Module : System.Posix.User.Common-- Copyright : (c) The University of Glasgow 2002-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : non-portable (requires POSIX)---- POSIX user\/group support-------------------------------------------------------------------------------moduleSystem.Posix.User.CommonwhereimportData.ByteString(ByteString)importSystem.Posix.Types{-# LINE 25 "System/Posix/User/Common.hsc" #-}importForeign.PtrimportForeign.MarshalimportForeign.StorableimportData.ByteString(packCString)-- internal typesdata{-# CTYPE"struct passwd"#-}CPasswd data{-# CTYPE"struct group"#-}CGroup dataLKUPTYPE =GETONE |GETALL unpackGroupEntry ::PtrCGroup ->IOGroupEntry unpackGroupEntry :: Ptr CGroup -> IO GroupEntry
unpackGroupEntry Ptr CGroup
ptr =doByteString
name <-((\Ptr CGroup
hsc_ptr ->Ptr CGroup -> Int -> IO CString
forall b. Ptr b -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOffPtr CGroup
hsc_ptr Int
0))Ptr CGroup
ptr IO CString -> (CString -> IO ByteString) -> IO ByteString
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=CString -> IO ByteString
packCString{-# LINE 39 "System/Posix/User/Common.hsc" #-}passwd<-((\hsc_ptr->peekByteOffhsc_ptr8))ptr>>=packCString{-# LINE 40 "System/Posix/User/Common.hsc" #-}gid<-((\hsc_ptr->peekByteOffhsc_ptr16))ptr{-# LINE 41 "System/Posix/User/Common.hsc" #-}mem<-((\hsc_ptr->peekByteOffhsc_ptr24))ptr{-# LINE 42 "System/Posix/User/Common.hsc" #-}members<-peekArray0nullPtrmem>>=mapMpackCStringGroupEntry -> IO GroupEntry
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(ByteString -> ByteString -> GroupID -> [ByteString] -> GroupEntry
GroupEntry ByteString
name ByteString
passwd GroupID
gid [ByteString]
members )unpackUserEntry ::PtrCPasswd ->IOUserEntry unpackUserEntry :: Ptr CPasswd -> IO UserEntry
unpackUserEntry Ptr CPasswd
ptr =doByteString
name <-((\Ptr CPasswd
hsc_ptr ->Ptr CPasswd -> Int -> IO CString
forall b. Ptr b -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOffPtr CPasswd
hsc_ptr Int
0))Ptr CPasswd
ptr IO CString -> (CString -> IO ByteString) -> IO ByteString
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=CString -> IO ByteString
packCString{-# LINE 48 "System/Posix/User/Common.hsc" #-}passwd<-((\hsc_ptr->peekByteOffhsc_ptr8))ptr>>=packCString{-# LINE 49 "System/Posix/User/Common.hsc" #-}uid<-((\hsc_ptr->peekByteOffhsc_ptr16))ptr{-# LINE 50 "System/Posix/User/Common.hsc" #-}gid<-((\hsc_ptr->peekByteOffhsc_ptr20))ptr{-# LINE 51 "System/Posix/User/Common.hsc" #-}{-# LINE 54 "System/Posix/User/Common.hsc" #-}ByteString
gecos <-((\Ptr CPasswd
hsc_ptr ->Ptr CPasswd -> Int -> IO CString
forall b. Ptr b -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOffPtr CPasswd
hsc_ptr Int
24))Ptr CPasswd
ptr IO CString -> (CString -> IO ByteString) -> IO ByteString
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=CString -> IO ByteString
packCString{-# LINE 55 "System/Posix/User/Common.hsc" #-}{-# LINE 56 "System/Posix/User/Common.hsc" #-}dir<-((\hsc_ptr->peekByteOffhsc_ptr32))ptr>>=packCString{-# LINE 57 "System/Posix/User/Common.hsc" #-}shell<-((\hsc_ptr->peekByteOffhsc_ptr40))ptr>>=packCString{-# LINE 58 "System/Posix/User/Common.hsc" #-}return(UserEntrynamepasswduidgidgecosdirshell){-# LINE 61 "System/Posix/User/Common.hsc" #-}dataUserEntry =UserEntry {UserEntry -> ByteString
userName ::ByteString,-- ^ Textual name of this user (pw_name)UserEntry -> ByteString
userPassword ::ByteString,-- ^ Password -- may be empty or fake if shadow is in use (pw_passwd)UserEntry -> UserID
userID ::UserID,-- ^ Numeric ID for this user (pw_uid)UserEntry -> GroupID
userGroupID ::GroupID,-- ^ Primary group ID (pw_gid)UserEntry -> ByteString
userGecos ::ByteString,-- ^ Usually the real name for the user (pw_gecos)UserEntry -> ByteString
homeDirectory ::ByteString,-- ^ Home directory (pw_dir)UserEntry -> ByteString
userShell ::ByteString-- ^ Default shell (pw_shell)}deriving(Int -> UserEntry -> ShowS
[UserEntry] -> ShowS
UserEntry -> String
(Int -> UserEntry -> ShowS)
-> (UserEntry -> String)
-> ([UserEntry] -> ShowS)
-> Show UserEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserEntry -> ShowS
showsPrec :: Int -> UserEntry -> ShowS
$cshow :: UserEntry -> String
show :: UserEntry -> String
$cshowList :: [UserEntry] -> ShowS
showList :: [UserEntry] -> ShowS
Show,ReadPrec [UserEntry]
ReadPrec UserEntry
Int -> ReadS UserEntry
ReadS [UserEntry]
(Int -> ReadS UserEntry)
-> ReadS [UserEntry]
-> ReadPrec UserEntry
-> ReadPrec [UserEntry]
-> Read UserEntry
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UserEntry
readsPrec :: Int -> ReadS UserEntry
$creadList :: ReadS [UserEntry]
readList :: ReadS [UserEntry]
$creadPrec :: ReadPrec UserEntry
readPrec :: ReadPrec UserEntry
$creadListPrec :: ReadPrec [UserEntry]
readListPrec :: ReadPrec [UserEntry]
Read,UserEntry -> UserEntry -> Bool
(UserEntry -> UserEntry -> Bool)
-> (UserEntry -> UserEntry -> Bool) -> Eq UserEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UserEntry -> UserEntry -> Bool
== :: UserEntry -> UserEntry -> Bool
$c/= :: UserEntry -> UserEntry -> Bool
/= :: UserEntry -> UserEntry -> Bool
Eq)dataGroupEntry =GroupEntry {GroupEntry -> ByteString
groupName ::ByteString,-- ^ The name of this group (gr_name)GroupEntry -> ByteString
groupPassword ::ByteString,-- ^ The password for this group (gr_passwd)GroupEntry -> GroupID
groupID ::GroupID,-- ^ The unique numeric ID for this group (gr_gid)GroupEntry -> [ByteString]
groupMembers ::[ByteString]-- ^ A list of zero or more usernames that are members (gr_mem)}deriving(Int -> GroupEntry -> ShowS
[GroupEntry] -> ShowS
GroupEntry -> String
(Int -> GroupEntry -> ShowS)
-> (GroupEntry -> String)
-> ([GroupEntry] -> ShowS)
-> Show GroupEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GroupEntry -> ShowS
showsPrec :: Int -> GroupEntry -> ShowS
$cshow :: GroupEntry -> String
show :: GroupEntry -> String
$cshowList :: [GroupEntry] -> ShowS
showList :: [GroupEntry] -> ShowS
Show,ReadPrec [GroupEntry]
ReadPrec GroupEntry
Int -> ReadS GroupEntry
ReadS [GroupEntry]
(Int -> ReadS GroupEntry)
-> ReadS [GroupEntry]
-> ReadPrec GroupEntry
-> ReadPrec [GroupEntry]
-> Read GroupEntry
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GroupEntry
readsPrec :: Int -> ReadS GroupEntry
$creadList :: ReadS [GroupEntry]
readList :: ReadS [GroupEntry]
$creadPrec :: ReadPrec GroupEntry
readPrec :: ReadPrec GroupEntry
$creadListPrec :: ReadPrec [GroupEntry]
readListPrec :: ReadPrec [GroupEntry]
Read,GroupEntry -> GroupEntry -> Bool
(GroupEntry -> GroupEntry -> Bool)
-> (GroupEntry -> GroupEntry -> Bool) -> Eq GroupEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GroupEntry -> GroupEntry -> Bool
== :: GroupEntry -> GroupEntry -> Bool
$c/= :: GroupEntry -> GroupEntry -> Bool
/= :: GroupEntry -> GroupEntry -> Bool
Eq)

AltStyle によって変換されたページ (->オリジナル) /