{-# LINE 1 "Network/Socket/Unix.hsc" #-}{-# LANGUAGE CPP #-}
#include "HsNetDef.h"
moduleNetwork.Socket.Unix(isUnixDomainSocketAvailable,socketPair,sendFd,recvFd,getPeerCredential,getPeerCred,getPeerEid)whereimportSystem.Posix.Types(Fd(..))importNetwork.Socket.BufferimportNetwork.Socket.Imports{-# LINE 21 "Network/Socket/Unix.hsc" #-}importNetwork.Socket.Posix.Cmsg{-# LINE 23 "Network/Socket/Unix.hsc" #-}importNetwork.Socket.Types{-# LINE 28 "Network/Socket/Unix.hsc" #-}{-# LINE 31 "Network/Socket/Unix.hsc" #-}{-# LINE 32 "Network/Socket/Unix.hsc" #-}importForeign.Marshal.Alloc(allocaBytes)importForeign.Marshal.Array(peekArray)importNetwork.Socket.FcntlimportNetwork.Socket.Internal{-# LINE 38 "Network/Socket/Unix.hsc" #-}{-# LINE 39 "Network/Socket/Unix.hsc" #-}importNetwork.Socket.Options{-# LINE 41 "Network/Socket/Unix.hsc" #-}-- | Getting process ID, user ID and group ID for UNIX-domain sockets.---- This is implemented with SO_PEERCRED on Linux and getpeereid()-- on BSD variants. Unfortunately, on some BSD variants-- getpeereid() returns unexpected results, rather than an error,-- for AF_INET sockets. It is the user's responsibility to make sure-- that the socket is a UNIX-domain socket.-- Also, on some BSD variants, getpeereid() does not return credentials-- for sockets created via 'socketPair', only separately created and then-- explicitly connected UNIX-domain sockets work on such systems.---- Since 2.7.0.0.getPeerCredential::Socket->IO(MaybeCUInt,MaybeCUInt,MaybeCUInt){-# LINE 56 "Network/Socket/Unix.hsc" #-}getPeerCredentialsock=do(pid,uid,gid)<-getPeerCredsockifuid==maxBoundthenreturn(Nothing,Nothing,Nothing)elsereturn(Justpid,Justuid,Justgid){-# LINE 72 "Network/Socket/Unix.hsc" #-}-- | Returns the processID, userID and groupID of the peer of-- a UNIX-domain socket.---- Only available on platforms that support SO_PEERCRED.getPeerCred::Socket->IO(CUInt,CUInt,CUInt){-# LINE 79 "Network/Socket/Unix.hsc" #-}getPeerCreds=doletopt=SockOpt(1)(17){-# LINE 81 "Network/Socket/Unix.hsc" #-}PeerCredcred<-getSockOptsoptreturncrednewtypePeerCred=PeerCred(CUInt,CUInt,CUInt)instanceStorablePeerCredwheresizeOf_=(12){-# LINE 87 "Network/Socket/Unix.hsc" #-}alignment_=alignment(0::CInt)poke__=return()peekp=dopid<-((\hsc_ptr->peekByteOffhsc_ptr0))p{-# LINE 91 "Network/Socket/Unix.hsc" #-}uid<-((\hsc_ptr->peekByteOffhsc_ptr4))p{-# LINE 92 "Network/Socket/Unix.hsc" #-}gid<-((\hsc_ptr->peekByteOffhsc_ptr8))p{-# LINE 93 "Network/Socket/Unix.hsc" #-}return$PeerCred(pid,uid,gid){-# LINE 97 "Network/Socket/Unix.hsc" #-}{-# DeprecatedgetPeerCred"Use getPeerCredential instead"#-}-- | Returns the userID and groupID of the peer of-- a UNIX-domain socket.---- Only available on platforms that support getpeereid().getPeerEid::Socket->IO(CUInt,CUInt){-# LINE 118 "Network/Socket/Unix.hsc" #-}getPeerEid_=return(0,0){-# LINE 120 "Network/Socket/Unix.hsc" #-}{-# DeprecatedgetPeerEid"Use getPeerCredential instead"#-}-- | Whether or not UNIX-domain sockets are available.---- Since 2.7.0.0.isUnixDomainSocketAvailable::Bool{-# LINE 128 "Network/Socket/Unix.hsc" #-}isUnixDomainSocketAvailable=True{-# LINE 132 "Network/Socket/Unix.hsc" #-}dataNullSockAddr=NullSockAddrinstanceSocketAddressNullSockAddrwheresizeOfSocketAddress_=0peekSocketAddress_=returnNullSockAddrpokeSocketAddress__=return()-- | Send a file descriptor over a UNIX-domain socket.-- Use this function in the case where 'isUnixDomainSocketAvailable' is-- 'True'.sendFd::Socket->CInt->IO(){-# LINE 145 "Network/Socket/Unix.hsc" #-}sendFdsoutfd=void$allocaBytesdummyBufSize$\buf->doletcmsg=encodeCmsg$FdoutfdsendBufMsgsNullSockAddr[(buf,dummyBufSize)][cmsg]memptywheredummyBufSize=1{-# LINE 153 "Network/Socket/Unix.hsc" #-}-- | Receive a file descriptor over a UNIX-domain socket. Note that the resulting-- file descriptor may have to be put into non-blocking mode in order to be-- used safely. See 'setNonBlockIfNeeded'.-- Use this function in the case where 'isUnixDomainSocketAvailable' is-- 'True'.recvFd::Socket->IOCInt{-# LINE 161 "Network/Socket/Unix.hsc" #-}recvFds=allocaBytesdummyBufSize$\buf->do(NullSockAddr,_,cmsgs,_)<-recvBufMsgs[(buf,dummyBufSize)]32memptycase(lookupCmsgCmsgIdFdcmsgs>>=decodeCmsg)::MaybeFdofNothing->return(-1)Just(Fdfd)->returnfdwheredummyBufSize=16{-# LINE 171 "Network/Socket/Unix.hsc" #-}-- | Build a pair of connected socket objects.-- For portability, use this function in the case-- where 'isUnixDomainSocketAvailable' is 'True'-- and specify 'AF_UNIX' to the first argument.socketPair::Family-- Family Name (usually AF_UNIX)->SocketType-- Socket Type (usually Stream)->ProtocolNumber-- Protocol Number->IO(Socket,Socket)-- unnamed and connected.{-# LINE 181 "Network/Socket/Unix.hsc" #-}socketPairfamilystypeprotocol=allocaBytes(2*sizeOf(1::CInt))$\fdArr->doletc_stype=packSocketTypestype_rc<-throwSocketErrorIfMinus1Retry"Network.Socket.socketpair"$c_socketpair(packFamilyfamily)c_stypeprotocolfdArr[fd1,fd2]<-peekArray2fdArrsetNonBlockIfNeededfd1setNonBlockIfNeededfd2s1<-mkSocketfd1s2<-mkSocketfd2return(s1,s2)foreignimportccallunsafe"socketpair"c_socketpair::CInt->CInt->CInt->PtrCInt->IOCInt{-# LINE 198 "Network/Socket/Unix.hsc" #-}

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