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

Used for button press and button release events. The
@type field will be one of %GDK_BUTTON_PRESS,
%GDK_2BUTTON_PRESS, %GDK_3BUTTON_PRESS or %GDK_BUTTON_RELEASE,

Double and triple-clicks result in a sequence of events being received.
For double-clicks the order of events will be:

- %GDK_BUTTON_PRESS
- %GDK_BUTTON_RELEASE
- %GDK_BUTTON_PRESS
- %GDK_2BUTTON_PRESS
- %GDK_BUTTON_RELEASE

Note that the first click is received just like a normal
button press, while the second click results in a %GDK_2BUTTON_PRESS
being received just after the %GDK_BUTTON_PRESS.

Triple-clicks are very similar to double-clicks, except that
%GDK_3BUTTON_PRESS is inserted after the third click. The order of the
events is:

- %GDK_BUTTON_PRESS
- %GDK_BUTTON_RELEASE
- %GDK_BUTTON_PRESS
- %GDK_2BUTTON_PRESS
- %GDK_BUTTON_RELEASE
- %GDK_BUTTON_PRESS
- %GDK_3BUTTON_PRESS
- %GDK_BUTTON_RELEASE

For a double click to occur, the second button press must occur within
1/4 of a second of the first. For a triple click to occur, the third
button press must also occur within 1/2 second of the first button press.
-}

module GI.Gdk.Structs.EventButton
    ( 

-- * Exported types
    EventButton(..)                         ,
    noEventButton                           ,


 -- * Properties
-- ** Axes
    eventButtonReadAxes                     ,


-- ** Button
    eventButtonReadButton                   ,


-- ** Device
    eventButtonReadDevice                   ,


-- ** SendEvent
    eventButtonReadSendEvent                ,


-- ** State
    eventButtonReadState                    ,


-- ** Time
    eventButtonReadTime                     ,


-- ** Type
    eventButtonReadType                     ,


-- ** Window
    eventButtonReadWindow                   ,


-- ** X
    eventButtonReadX                        ,


-- ** XRoot
    eventButtonReadXRoot                    ,


-- ** Y
    eventButtonReadY                        ,


-- ** YRoot
    eventButtonReadYRoot                    ,




    ) 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 EventButton = EventButton (ForeignPtr EventButton)
noEventButton :: Maybe EventButton
noEventButton = Nothing

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

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

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

eventButtonReadTime :: EventButton -> IO Word32
eventButtonReadTime s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: IO Word32
    return val

eventButtonReadX :: EventButton -> IO Double
eventButtonReadX s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CDouble
    let val' = realToFrac val
    return val'

eventButtonReadY :: EventButton -> IO Double
eventButtonReadY s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO CDouble
    let val' = realToFrac val
    return val'

eventButtonReadAxes :: EventButton -> IO Double
eventButtonReadAxes s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CDouble
    let val' = realToFrac val
    return val'

eventButtonReadState :: EventButton -> IO [ModifierType]
eventButtonReadState s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO CUInt
    let val' = wordToGFlags val
    return val'

eventButtonReadButton :: EventButton -> IO Word32
eventButtonReadButton s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 52) :: IO Word32
    return val

eventButtonReadDevice :: EventButton -> IO Device
eventButtonReadDevice s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO (Ptr Device)
    val' <- (newObject Device) val
    return val'

eventButtonReadXRoot :: EventButton -> IO Double
eventButtonReadXRoot s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO CDouble
    let val' = realToFrac val
    return val'

eventButtonReadYRoot :: EventButton -> IO Double
eventButtonReadYRoot s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 72) :: IO CDouble
    let val' = realToFrac val
    return val'