posix-api-0.7.2.0: posix bindings
Safe HaskellSafe-Inferred
LanguageHaskell2010

Linux.Epoll

Synopsis

Functions

Create

uninterruptibleCreate Source #

Arguments

:: CInt

Size, ignored since Linux 2.6.8

-> IO (Either Errno Fd) 

Wait

waitMutablePrimArray Source #

Arguments

:: Fd

EPoll file descriptor

-> MutablePrimArray RealWorld (Event 'Response a)

Event buffer, must be pinned

-> CInt

Maximum events

-> CInt

Timeout in milliseconds, use -1 to block forever.

-> IO (Either Errno CInt)

Number of events received

Wait for an I/O event on an epoll file descriptor. The Linux man page includes more details. The event buffer must be a pinned byte array.

uninterruptibleWaitMutablePrimArray Source #

Arguments

:: Fd

EPoll file descriptor

-> MutablePrimArray RealWorld (Event 'Response a)

Event buffer

-> CInt

Maximum events

-> IO (Either Errno CInt)

Number of events received

Wait for an I/O event on an epoll file descriptor. The Linux man page includes more details. The timeout argument is omitted since it is nonsense to choose anything other than 0 when using the unsafe FFI.

Control

uninterruptibleControlMutablePrimArray Source #

Arguments

:: Fd

EPoll file descriptor (epfd)

-> ControlOperation

Operation: EPOLL_CTL_ADD, EPOLL_CTL_MOD, or EPOLL_CTL_DEL

-> Fd

File descriptor whose registration will be affected

-> MutablePrimArray RealWorld (Event 'Request a)

A single event. This is read from, not written to.

-> IO (Either Errno ()) 

Add, modify, or remove entries in the interest list of the epoll instance referred to by the file descriptor epfd. Linux man page includes more details.

Types

newtype EpollFlags Source #

Constructors

EpollFlags CInt 

Instances

Instances details
Monoid EpollFlags Source # 
Instance details

Defined in Linux.Epoll.Types

Semigroup EpollFlags Source # 
Instance details

Defined in Linux.Epoll.Types

Bits EpollFlags Source # 
Instance details

Defined in Linux.Epoll.Types

Eq EpollFlags Source # 
Instance details

Defined in Linux.Epoll.Types

newtype ControlOperation Source #

Constructors

ControlOperation CInt 

Instances

Instances details
Eq ControlOperation Source # 
Instance details

Defined in Linux.Epoll.Types

newtype Events :: Exchange -> Type where Source #

Constructors

Events :: Word32 -> Events e 

Instances

Instances details
Storable (Events a) Source # 
Instance details

Defined in Linux.Epoll.Types

Methods

sizeOf :: Events a -> Int #

alignment :: Events a -> Int #

peekElemOff :: Ptr (Events a) -> Int -> IO (Events a) #

pokeElemOff :: Ptr (Events a) -> Int -> Events a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Events a) #

pokeByteOff :: Ptr b -> Int -> Events a -> IO () #

peek :: Ptr (Events a) -> IO (Events a) #

poke :: Ptr (Events a) -> Events a -> IO () #

Monoid (Events e) Source # 
Instance details

Defined in Linux.Epoll.Types

Methods

mempty :: Events e #

mappend :: Events e -> Events e -> Events e #

mconcat :: [Events e] -> Events e #

Semigroup (Events e) Source # 
Instance details

Defined in Linux.Epoll.Types

Methods

(<>) :: Events e -> Events e -> Events e #

sconcat :: NonEmpty (Events e) -> Events e #

stimes :: Integral b => b -> Events e -> Events e #

Bits (Events a) Source # 
Instance details

Defined in Linux.Epoll.Types

Methods

(.&.) :: Events a -> Events a -> Events a #

(.|.) :: Events a -> Events a -> Events a #

xor :: Events a -> Events a -> Events a #

complement :: Events a -> Events a #

shift :: Events a -> Int -> Events a #

rotate :: Events a -> Int -> Events a #

zeroBits :: Events a #

bit :: Int -> Events a #

setBit :: Events a -> Int -> Events a #

clearBit :: Events a -> Int -> Events a #

complementBit :: Events a -> Int -> Events a #

testBit :: Events a -> Int -> Bool #

bitSizeMaybe :: Events a -> Maybe Int #

bitSize :: Events a -> Int #

isSigned :: Events a -> Bool #

shiftL :: Events a -> Int -> Events a #

unsafeShiftL :: Events a -> Int -> Events a #

shiftR :: Events a -> Int -> Events a #

unsafeShiftR :: Events a -> Int -> Events a #

rotateL :: Events a -> Int -> Events a #

rotateR :: Events a -> Int -> Events a #

popCount :: Events a -> Int #

Eq (Events a) Source # 
Instance details

Defined in Linux.Epoll.Types

Methods

(==) :: Events a -> Events a -> Bool #

(/=) :: Events a -> Events a -> Bool #

Prim (Events a) Source # 
Instance details

Defined in Linux.Epoll.Types

data Event :: Exchange -> Type -> Type where Source #

A data type corresponding to struct epoll_event. Linux defines this as:

typedef union epoll_data {
    void    *ptr;
    int      fd;
    uint32_t u32;
    uint64_t u64;
} epoll_data_t;

struct epoll_event {
    uint32_t     events; /* Epoll events */
    epoll_data_t data;   /* User data variable */
};

It is a little difficult to capture what this type conveys, but we make an attempt. The second argument to the Event type constructor is either Addr, Fd, Word32, or Word64. This corresponds to the four possibilities in the epoll_data union type. As long as the user monomorphizes this type when using it, there should not be any performance penalty for the flexibility afforded by this approach.

Constructors

Event 

Fields

  • :: { events :: !(Events e)

    Epoll events

  •    , payload :: !a

    User data variable, named data in struct epoll_event.

  •    } -> Event e a
     

Instances

Instances details
PrimEpollData a => Prim (Event e a) Source # 
Instance details

Defined in Linux.Epoll.Types

Methods

sizeOfType# :: Proxy (Event e a) -> Int# #

sizeOf# :: Event e a -> Int# #

alignmentOfType# :: Proxy (Event e a) -> Int# #

alignment# :: Event e a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Event e a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Event e a #) #

writeByteArray# :: MutableByteArray# s -> Int# -> Event e a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Event e a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Event e a #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Event e a #) #

writeOffAddr# :: Addr# -> Int# -> Event e a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Event e a -> State# s -> State# s #

data Exchange Source #

Constructors

Request 
Response 

Classes

class PrimEpollData a Source #

Minimal complete definition

indexByteArrayEpoll, readByteArrayEpoll, writeByteArrayEpoll, indexOffAddrEpoll, readOffAddrEpoll, writeOffAddrEpoll

Instances

Instances details
PrimEpollData Word64 Source #

Since epoll_event includes an unaligned 64-bit word, it is difficult to use hsc2hs to generate the marshalling code. Consequently, the offsets of events and data are currently hardcoded. Open an issue in this causes a problem on your platform.

Instance details

Defined in Linux.Epoll.Types

Methods

indexByteArrayEpoll :: forall (e :: Exchange). ByteArray# -> Int# -> Event e Word64

readByteArrayEpoll :: forall s (e :: Exchange). MutableByteArray# s -> Int# -> State# s -> (# State# s, Event e Word64 #)

writeByteArrayEpoll :: forall s (e :: Exchange). MutableByteArray# s -> Int# -> Event e Word64 -> State# s -> State# s

indexOffAddrEpoll :: forall (e :: Exchange). Addr# -> Int# -> Event e Word64

readOffAddrEpoll :: forall s (e :: Exchange). Addr# -> Int# -> State# s -> (# State# s, Event e Word64 #)

writeOffAddrEpoll :: forall (e :: Exchange) s. Addr# -> Int# -> Event e Word64 -> State# s -> State# s

PrimEpollData Fd Source # 
Instance details

Defined in Linux.Epoll.Types

Methods

indexByteArrayEpoll :: forall (e :: Exchange). ByteArray# -> Int# -> Event e Fd

readByteArrayEpoll :: forall s (e :: Exchange). MutableByteArray# s -> Int# -> State# s -> (# State# s, Event e Fd #)

writeByteArrayEpoll :: forall s (e :: Exchange). MutableByteArray# s -> Int# -> Event e Fd -> State# s -> State# s

indexOffAddrEpoll :: forall (e :: Exchange). Addr# -> Int# -> Event e Fd

readOffAddrEpoll :: forall s (e :: Exchange). Addr# -> Int# -> State# s -> (# State# s, Event e Fd #)

writeOffAddrEpoll :: forall (e :: Exchange) s. Addr# -> Int# -> Event e Fd -> State# s -> State# s

Constants

closeOnExec :: EpollFlags Source #

The EPOLL_CLOEXEC flag.

add :: ControlOperation Source #

The EPOLL_CTL_ADD control operation.

modify :: ControlOperation Source #

The EPOLL_CTL_MOD control operation.

delete :: ControlOperation Source #

The EPOLL_CTL_DEL control operation.

input :: Events e Source #

The EPOLLIN event. Can appear in a request or a response.

output :: Events e Source #

The EPOLLOUT event. Can appear in a request or a response.

priority :: Events e Source #

The EPOLLPRI event. Can appear in a request or a response.

hangup :: Events Response Source #

The EPOLLHUP event. The epoll_ctl documentation says "epoll_wait will always wait for this event; it is not necessary to set it in events". Consequently, in this library, it has been marked as only appearing in Response positions.

readHangup :: Events e Source #

The EPOLLRDHUP event. Can appear in a request or a response.

error :: Events Response Source #

The EPOLLERR event. The epoll_ctl documentation says "epoll_wait will always wait for this event; it is not necessary to set it in events". Consequently, in this library, it has been marked as only appearing in Response positions.

edgeTriggered :: Events Request Source #

The EPOLLET event. Only appears in requests.

Events Combinators

containsAnyEvents :: Events e -> Events e -> Bool Source #

Does the first event set contain any of the events from the second one?

containsAllEvents :: Events e -> Events e -> Bool Source #

Does the first event set entirely contain the second one? That is, is the second argument a subset of the first?

Marshalling

peekEventEvents :: Addr -> IO (Events e) Source #

Read events from struct epoll_event.

peekEventDataFd :: Addr -> IO Fd Source #

Read data.fd from struct epoll_event.

peekEventDataPtr :: Addr -> IO Addr Source #

Read data.ptr from struct epoll_event.

peekEventDataU32 :: Addr -> IO Word32 Source #

Read data.u32 from struct epoll_event.

peekEventDataU64 :: Addr -> IO Word64 Source #

Read data.u64 from struct epoll_event.

pokeEventDataU64 :: Addr -> Word64 -> IO () Source #

Write data.u64 from struct epoll_event.