{- |
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 the pointer moves.
-}

module GI.Gdk.Structs.EventMotion
    ( 

-- * Exported types
    EventMotion(..)                         ,
    noEventMotion                           ,


 -- * Properties
-- ** Axes
    eventMotionReadAxes                     ,


-- ** Device
    eventMotionReadDevice                   ,


-- ** IsHint
    eventMotionReadIsHint                   ,


-- ** SendEvent
    eventMotionReadSendEvent                ,


-- ** State
    eventMotionReadState                    ,


-- ** Time
    eventMotionReadTime                     ,


-- ** Type
    eventMotionReadType                     ,


-- ** Window
    eventMotionReadWindow                   ,


-- ** X
    eventMotionReadX                        ,


-- ** XRoot
    eventMotionReadXRoot                    ,


-- ** Y
    eventMotionReadY                        ,


-- ** YRoot
    eventMotionReadYRoot                    ,




    ) 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 EventMotion = EventMotion (ForeignPtr EventMotion)
noEventMotion :: Maybe EventMotion
noEventMotion = Nothing

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

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

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

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

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

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

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

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

eventMotionReadIsHint :: EventMotion -> IO Int16
eventMotionReadIsHint s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 52) :: IO Int16
    return val

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

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

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