{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents a file descriptor, which events to poll for, and which events
-- occurred.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.GLib.Structs.PollFD
    ( 

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


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolvePollFDMethod                     ,
#endif




 -- * Properties
-- ** events #attr:events#
-- | a bitwise combination from t'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)
    pollFD_events                           ,
#endif
    setPollFDEvents                         ,


-- ** fd #attr:fd#
-- | the file descriptor to poll (or a HANDLE on Win32)

    getPollFDFd                             ,
#if defined(ENABLE_OVERLOADING)
    pollFD_fd                               ,
#endif
    setPollFDFd                             ,


-- ** revents #attr:revents#
-- | a bitwise combination of flags from t'GI.GLib.Flags.IOCondition', returned
--     from the @/poll()/@ function to indicate which events occurred.

    getPollFDRevents                        ,
#if defined(ENABLE_OVERLOADING)
    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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
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
import qualified GHC.OverloadedLabels as OL


-- | Memory-managed wrapper type.
newtype PollFD = PollFD (ManagedPtr PollFD)
    deriving (PollFD -> PollFD -> Bool
(PollFD -> PollFD -> Bool)
-> (PollFD -> PollFD -> Bool) -> Eq PollFD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollFD -> PollFD -> Bool
$c/= :: PollFD -> PollFD -> Bool
== :: PollFD -> PollFD -> Bool
$c== :: PollFD -> PollFD -> Bool
Eq)
foreign import ccall "g_pollfd_get_type" c_g_pollfd_get_type :: 
    IO GType

instance BoxedObject PollFD where
    boxedType :: PollFD -> IO GType
boxedType _ = IO GType
c_g_pollfd_get_type

-- | Convert 'PollFD' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue PollFD where
    toGValue :: PollFD -> IO GValue
toGValue o :: PollFD
o = do
        GType
gtype <- IO GType
c_g_pollfd_get_type
        PollFD -> (Ptr PollFD -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PollFD
o (GType -> (GValue -> Ptr PollFD -> IO ()) -> Ptr PollFD -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr PollFD -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO PollFD
fromGValue gv :: GValue
gv = do
        Ptr PollFD
ptr <- GValue -> IO (Ptr PollFD)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr PollFD)
        (ManagedPtr PollFD -> PollFD) -> Ptr PollFD -> IO PollFD
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr PollFD -> PollFD
PollFD Ptr PollFD
ptr
        
    

-- | Construct a `PollFD` struct initialized to zero.
newZeroPollFD :: MonadIO m => m PollFD
newZeroPollFD :: m PollFD
newZeroPollFD = IO PollFD -> m PollFD
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PollFD -> m PollFD) -> IO PollFD -> m PollFD
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr PollFD)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 IO (Ptr PollFD) -> (Ptr PollFD -> IO PollFD) -> IO PollFD
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr PollFD -> PollFD) -> Ptr PollFD -> IO PollFD
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr PollFD -> PollFD
PollFD

instance tag ~ 'AttrSet => Constructible PollFD tag where
    new :: (ManagedPtr PollFD -> PollFD) -> [AttrOp PollFD tag] -> m PollFD
new _ attrs :: [AttrOp PollFD tag]
attrs = do
        PollFD
o <- m PollFD
forall (m :: * -> *). MonadIO m => m PollFD
newZeroPollFD
        PollFD -> [AttrOp PollFD 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set PollFD
o [AttrOp PollFD tag]
[AttrOp PollFD 'AttrSet]
attrs
        PollFD -> m PollFD
forall (m :: * -> *) a. Monad m => a -> m a
return PollFD
o


-- | A convenience alias for `Nothing` :: `Maybe` `PollFD`.
noPollFD :: Maybe PollFD
noPollFD :: Maybe PollFD
noPollFD = Maybe PollFD
forall a. Maybe a
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 :: PollFD -> m Int32
getPollFDFd s :: PollFD
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ PollFD -> (Ptr PollFD -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PollFD
s ((Ptr PollFD -> IO Int32) -> IO Int32)
-> (Ptr PollFD -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PollFD
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr PollFD
ptr Ptr PollFD -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
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 :: PollFD -> Int32 -> m ()
setPollFDFd s :: PollFD
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ PollFD -> (Ptr PollFD -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PollFD
s ((Ptr PollFD -> IO ()) -> IO ()) -> (Ptr PollFD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PollFD
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PollFD
ptr Ptr PollFD -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Int32
val :: Int32)

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

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 :: PollFD -> m Word16
getPollFDEvents s :: PollFD
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ PollFD -> (Ptr PollFD -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PollFD
s ((Ptr PollFD -> IO Word16) -> IO Word16)
-> (Ptr PollFD -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PollFD
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr PollFD
ptr Ptr PollFD -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4) :: IO Word16
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
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 :: PollFD -> Word16 -> m ()
setPollFDEvents s :: PollFD
s val :: Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ PollFD -> (Ptr PollFD -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PollFD
s ((Ptr PollFD -> IO ()) -> IO ()) -> (Ptr PollFD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PollFD
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PollFD
ptr Ptr PollFD -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4) (Word16
val :: Word16)

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

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 :: PollFD -> m Word16
getPollFDRevents s :: PollFD
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ PollFD -> (Ptr PollFD -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PollFD
s ((Ptr PollFD -> IO Word16) -> IO Word16)
-> (Ptr PollFD -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PollFD
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr PollFD
ptr Ptr PollFD -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 6) :: IO Word16
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
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 :: PollFD -> Word16 -> m ()
setPollFDRevents s :: PollFD
s val :: Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ PollFD -> (Ptr PollFD -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PollFD
s ((Ptr PollFD -> IO ()) -> IO ()) -> (Ptr PollFD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PollFD
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PollFD
ptr Ptr PollFD -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 6) (Word16
val :: Word16)

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

pollFD_revents :: AttrLabelProxy "revents"
pollFD_revents = AttrLabelProxy

#endif



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

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

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

#endif