{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

Represents a file descriptor, which events to poll for, and which events
occurred.
-}

module GI.GLib.Structs.PollFD
    ( 

-- * Exported types
    PollFD(..)                              ,
    newZeroPollFD                           ,
    noPollFD                                ,


 -- * Properties
-- ** events #attr:events#
{- | a bitwise combination from 'GI.GLib.Flags.IOCondition', specifying which
    events should be polled for. Typically for reading from a file
    descriptor you would use 'GI.GLib.Flags.IOConditionIn' | 'GI.GLib.Flags.IOConditionHup' | 'GI.GLib.Flags.IOConditionErr', and
    for writing you would use 'GI.GLib.Flags.IOConditionOut' | 'GI.GLib.Flags.IOConditionErr'.
-}
    getPollFDEvents                         ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pollFD_events                           ,
#endif
    setPollFDEvents                         ,


-- ** fd #attr:fd#
{- | the file descriptor to poll (or a HANDLE on Win32)
-}
    getPollFDFd                             ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pollFD_fd                               ,
#endif
    setPollFDFd                             ,


-- ** revents #attr:revents#
{- | a bitwise combination of flags from 'GI.GLib.Flags.IOCondition', returned
    from the @/poll()/@ function to indicate which events occurred.
-}
    getPollFDRevents                        ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    pollFD_revents                          ,
#endif
    setPollFDRevents                        ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP


-- | Memory-managed wrapper type.
newtype PollFD = PollFD (ManagedPtr PollFD)
foreign import ccall "g_pollfd_get_type" c_g_pollfd_get_type :: 
    IO GType

instance BoxedObject PollFD where
    boxedType _ = c_g_pollfd_get_type

-- | Construct a `PollFD` struct initialized to zero.
newZeroPollFD :: MonadIO m => m PollFD
newZeroPollFD = liftIO $ callocBoxedBytes 8 >>= wrapBoxed PollFD

instance tag ~ 'AttrSet => Constructible PollFD tag where
    new _ attrs = do
        o <- newZeroPollFD
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `PollFD`.
noPollFD :: Maybe PollFD
noPollFD = Nothing

{- |
Get the value of the “@fd@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' pollFD #fd
@
-}
getPollFDFd :: MonadIO m => PollFD -> m Int32
getPollFDFd s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int32
    return val

{- |
Set the value of the “@fd@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' pollFD [ #fd 'Data.GI.Base.Attributes.:=' value ]
@
-}
setPollFDFd :: MonadIO m => PollFD -> Int32 -> m ()
setPollFDFd s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Int32)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PollFDFdFieldInfo
instance AttrInfo PollFDFdFieldInfo where
    type AttrAllowedOps PollFDFdFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint PollFDFdFieldInfo = (~) Int32
    type AttrBaseTypeConstraint PollFDFdFieldInfo = (~) PollFD
    type AttrGetType PollFDFdFieldInfo = Int32
    type AttrLabel PollFDFdFieldInfo = "fd"
    type AttrOrigin PollFDFdFieldInfo = PollFD
    attrGet _ = getPollFDFd
    attrSet _ = setPollFDFd
    attrConstruct = undefined
    attrClear _ = undefined

pollFD_fd :: AttrLabelProxy "fd"
pollFD_fd = AttrLabelProxy

#endif


{- |
Get the value of the “@events@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' pollFD #events
@
-}
getPollFDEvents :: MonadIO m => PollFD -> m Word16
getPollFDEvents s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO Word16
    return val

{- |
Set the value of the “@events@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' pollFD [ #events 'Data.GI.Base.Attributes.:=' value ]
@
-}
setPollFDEvents :: MonadIO m => PollFD -> Word16 -> m ()
setPollFDEvents s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 4) (val :: Word16)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PollFDEventsFieldInfo
instance AttrInfo PollFDEventsFieldInfo where
    type AttrAllowedOps PollFDEventsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint PollFDEventsFieldInfo = (~) Word16
    type AttrBaseTypeConstraint PollFDEventsFieldInfo = (~) PollFD
    type AttrGetType PollFDEventsFieldInfo = Word16
    type AttrLabel PollFDEventsFieldInfo = "events"
    type AttrOrigin PollFDEventsFieldInfo = PollFD
    attrGet _ = getPollFDEvents
    attrSet _ = setPollFDEvents
    attrConstruct = undefined
    attrClear _ = undefined

pollFD_events :: AttrLabelProxy "events"
pollFD_events = AttrLabelProxy

#endif


{- |
Get the value of the “@revents@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' pollFD #revents
@
-}
getPollFDRevents :: MonadIO m => PollFD -> m Word16
getPollFDRevents s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 6) :: IO Word16
    return val

{- |
Set the value of the “@revents@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' pollFD [ #revents 'Data.GI.Base.Attributes.:=' value ]
@
-}
setPollFDRevents :: MonadIO m => PollFD -> Word16 -> m ()
setPollFDRevents s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 6) (val :: Word16)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data PollFDReventsFieldInfo
instance AttrInfo PollFDReventsFieldInfo where
    type AttrAllowedOps PollFDReventsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint PollFDReventsFieldInfo = (~) Word16
    type AttrBaseTypeConstraint PollFDReventsFieldInfo = (~) PollFD
    type AttrGetType PollFDReventsFieldInfo = Word16
    type AttrLabel PollFDReventsFieldInfo = "revents"
    type AttrOrigin PollFDReventsFieldInfo = PollFD
    attrGet _ = getPollFDRevents
    attrSet _ = setPollFDRevents
    attrConstruct = undefined
    attrClear _ = undefined

pollFD_revents :: AttrLabelProxy "revents"
pollFD_revents = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList PollFD
type instance O.AttributeList PollFD = PollFDAttributeList
type PollFDAttributeList = ('[ '("fd", PollFDFdFieldInfo), '("events", PollFDEventsFieldInfo), '("revents", PollFDReventsFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolvePollFDMethod (t :: Symbol) (o :: *) :: * where
    ResolvePollFDMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePollFDMethod t PollFD, O.MethodInfo info PollFD p) => O.IsLabelProxy t (PollFD -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolvePollFDMethod t PollFD, O.MethodInfo info PollFD p) => O.IsLabel t (PollFD -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif

#endif