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

Generated when a selection is requested or ownership of a selection
is taken over by another client application.
-}

module GI.Gdk.Structs.EventSelection
    ( 

-- * Exported types
    EventSelection(..)                      ,
    noEventSelection                        ,


 -- * Properties
-- ** Property
    eventSelectionReadProperty              ,


-- ** Requestor
    eventSelectionReadRequestor             ,


-- ** Selection
    eventSelectionReadSelection             ,


-- ** SendEvent
    eventSelectionReadSendEvent             ,


-- ** Target
    eventSelectionReadTarget                ,


-- ** Time
    eventSelectionReadTime                  ,


-- ** Type
    eventSelectionReadType                  ,


-- ** Window
    eventSelectionReadWindow                ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gdk.Types
import GI.Gdk.Callbacks

newtype EventSelection = EventSelection (ForeignPtr EventSelection)
noEventSelection :: Maybe EventSelection
noEventSelection = Nothing

eventSelectionReadType :: EventSelection -> IO EventType
eventSelectionReadType s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

eventSelectionReadWindow :: EventSelection -> IO Window
eventSelectionReadWindow s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr Window)
    val' <- (newObject Window) val
    return val'

eventSelectionReadSendEvent :: EventSelection -> IO Int8
eventSelectionReadSendEvent s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int8
    return val

eventSelectionReadSelection :: EventSelection -> IO Atom
eventSelectionReadSelection s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (Ptr Atom)
    -- XXX Wrapping a foreign struct/union with no known destructor, leak?
    val' <- (\x -> Atom <$> newForeignPtr_ x) val
    return val'

eventSelectionReadTarget :: EventSelection -> IO Atom
eventSelectionReadTarget s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO (Ptr Atom)
    -- XXX Wrapping a foreign struct/union with no known destructor, leak?
    val' <- (\x -> Atom <$> newForeignPtr_ x) val
    return val'

eventSelectionReadProperty :: EventSelection -> IO Atom
eventSelectionReadProperty s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO (Ptr Atom)
    -- XXX Wrapping a foreign struct/union with no known destructor, leak?
    val' <- (\x -> Atom <$> newForeignPtr_ x) val
    return val'

eventSelectionReadTime :: EventSelection -> IO Word32
eventSelectionReadTime s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO Word32
    return val

eventSelectionReadRequestor :: EventSelection -> IO Window
eventSelectionReadRequestor s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO (Ptr Window)
    val' <- (newObject Window) val
    return val'