{-# LANGUAGE ForeignFunctionInterface #-} -- Primed functions work on ForeignPtrs, unprimed work on FdSets. module System.Posix.IO.Select.FdSet.Internal where import Foreign.ForeignPtr.Safe import Foreign.Ptr import Foreign.Marshal.Utils import Foreign.C.Types import System.Posix.Types import Misc -- NOT an instance of storable. We treat fdset as opaque, maintaing only a pointer. data FdSet = FdSet (ForeignPtr ()) Fd #include #include "cbits.h" #let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__) remove' :: Fd -> ForeignPtr () -> IO () remove' fd ptr = withForeignPtr ptr (c_fd_clr_wrapper (fromIntegral fd)) insert' :: Fd -> ForeignPtr () -> IO () insert' fd ptr = withForeignPtr ptr (c_fd_set_wrapper (fromIntegral fd)) elem' :: Fd -> ForeignPtr () -> IO CInt elem' fd ptr = withForeignPtr ptr (c_fd_isset_wrapper (fromIntegral fd)) pointer :: FdSet -> ForeignPtr () pointer (FdSet p _) = p allocate' :: IO (ForeignPtr ()) allocate' = mallocForeignPtrBytes #{size fd_set} -- debugging: putStrLn ("Allocating " ++ show #{size fd_set} ++ ".") >> -- Remove when finished testing. duplicate' :: ForeignPtr () -> IO (ForeignPtr ()) duplicate' ptr = allocate' >>= \newPtr -> withForeignPtr ptr (\ptr' -> withForeignPtr newPtr (\newPtr' -> copyBytes newPtr' ptr' #{size fd_set})) >> return newPtr c_FD_SETSIZE :: Fd c_FD_SETSIZE = #{const FD_SETSIZE} foreign import ccall "cbits.h fd_zero_wrapper" c_fd_zero_wrapper :: Ptr () -> IO () foreign import ccall "cbits.h fd_set_wrapper" c_fd_set_wrapper :: CInt -> Ptr () -> IO () foreign import ccall "cbits.h fd_clr_wrapper" c_fd_clr_wrapper :: CInt -> Ptr () -> IO () foreign import ccall "cbits.h fd_isset_wrapper" c_fd_isset_wrapper :: CInt -> Ptr () -> IO CInt