module System.Posix.Poll (
Fd(..),
Event(..),
Events,
inp, pri, out, err, hup, nVal,
) where
import Foreign.C.Types (CShort, )
import Foreign.Storable
(Storable(sizeOf, alignment, peek, poke),
peekByteOff, pokeByteOff, )
import qualified System.Posix.Types as Posix
import Data.Ix (Ix, range, index, inRange, rangeSize, )
import Data.Maybe (fromMaybe, )
import qualified Data.Ix.Enum as IxEnum
import qualified Data.EnumSet as EnumSet
data Event
= Other Int
| In
| Pri
| Out
| Err
| Hup
| NVal
deriving (Eq, Ord, Show)
eventFlagSet :: Event -> Events
eventFlagSet cap =
case cap of
Other n -> EnumSet.singletonByPosition n
In -> inp
Pri -> pri
Out -> out
Err -> err
Hup -> hup
NVal -> nVal
instance Enum Event where
fromEnum cap =
case cap of
Other n -> n
_ -> EnumSet.mostSignificantPosition (eventFlagSet cap)
toEnum n =
fromMaybe (Other n) $
lookup (EnumSet.singletonByPosition n) $
map (\ev -> (eventFlagSet ev, ev)) $
In :
Pri :
Out :
Err :
Hup :
NVal :
[]
instance Ix Event where
range = IxEnum.range
index = IxEnum.index
inRange = IxEnum.inRange
rangeSize = IxEnum.rangeSize
inp, pri, out, err, hup, nVal :: Events
inp = EnumSet.Cons 1
pri = EnumSet.Cons 2
out = EnumSet.Cons 4
err = EnumSet.Cons 8
hup = EnumSet.Cons 16
nVal = EnumSet.Cons 32
type Events = EnumSet.T CShort Event
data Fd = Fd
{ fd :: Posix.Fd
, events :: Events
, rEvents :: Events
}
instance Storable Fd where
sizeOf _ = (8)
alignment _ = 4
peek p = do
f <- (\hsc_ptr -> peekByteOff hsc_ptr 0) p
e <- (\hsc_ptr -> peekByteOff hsc_ptr 4) p
r <- (\hsc_ptr -> peekByteOff hsc_ptr 6) p
return $ Fd (Posix.Fd f) e r
poke p (Fd (Posix.Fd f) e r) = do
(\hsc_ptr -> pokeByteOff hsc_ptr 0) p f
(\hsc_ptr -> pokeByteOff hsc_ptr 4) p e
(\hsc_ptr -> pokeByteOff hsc_ptr 6) p r