{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An event related to a pad-based device.

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

module GI.Gdk.Objects.PadEvent
    ( 

-- * Exported types
    PadEvent(..)                            ,
    IsPadEvent                              ,
    toPadEvent                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [ref]("GI.Gdk.Objects.Event#g:method:ref"), [triggersContextMenu]("GI.Gdk.Objects.Event#g:method:triggersContextMenu"), [unref]("GI.Gdk.Objects.Event#g:method:unref").
-- 
-- ==== Getters
-- [getAxes]("GI.Gdk.Objects.Event#g:method:getAxes"), [getAxis]("GI.Gdk.Objects.Event#g:method:getAxis"), [getAxisValue]("GI.Gdk.Objects.PadEvent#g:method:getAxisValue"), [getButton]("GI.Gdk.Objects.PadEvent#g:method:getButton"), [getDevice]("GI.Gdk.Objects.Event#g:method:getDevice"), [getDeviceTool]("GI.Gdk.Objects.Event#g:method:getDeviceTool"), [getDisplay]("GI.Gdk.Objects.Event#g:method:getDisplay"), [getEventSequence]("GI.Gdk.Objects.Event#g:method:getEventSequence"), [getEventType]("GI.Gdk.Objects.Event#g:method:getEventType"), [getGroupMode]("GI.Gdk.Objects.PadEvent#g:method:getGroupMode"), [getHistory]("GI.Gdk.Objects.Event#g:method:getHistory"), [getModifierState]("GI.Gdk.Objects.Event#g:method:getModifierState"), [getPointerEmulated]("GI.Gdk.Objects.Event#g:method:getPointerEmulated"), [getPosition]("GI.Gdk.Objects.Event#g:method:getPosition"), [getSeat]("GI.Gdk.Objects.Event#g:method:getSeat"), [getSurface]("GI.Gdk.Objects.Event#g:method:getSurface"), [getTime]("GI.Gdk.Objects.Event#g:method:getTime").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolvePadEventMethod                   ,
#endif

-- ** getAxisValue #method:getAxisValue#

#if defined(ENABLE_OVERLOADING)
    PadEventGetAxisValueMethodInfo          ,
#endif
    padEventGetAxisValue                    ,


-- ** getButton #method:getButton#

#if defined(ENABLE_OVERLOADING)
    PadEventGetButtonMethodInfo             ,
#endif
    padEventGetButton                       ,


-- ** getGroupMode #method:getGroupMode#

#if defined(ENABLE_OVERLOADING)
    PadEventGetGroupModeMethodInfo          ,
#endif
    padEventGetGroupMode                    ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
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 Control.Monad.IO.Class as MIO
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
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.Gdk.Objects.Event as Gdk.Event

-- | Memory-managed wrapper type.
newtype PadEvent = PadEvent (SP.ManagedPtr PadEvent)
    deriving (PadEvent -> PadEvent -> Bool
(PadEvent -> PadEvent -> Bool)
-> (PadEvent -> PadEvent -> Bool) -> Eq PadEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PadEvent -> PadEvent -> Bool
$c/= :: PadEvent -> PadEvent -> Bool
== :: PadEvent -> PadEvent -> Bool
$c== :: PadEvent -> PadEvent -> Bool
Eq)

instance SP.ManagedPtrNewtype PadEvent where
    toManagedPtr :: PadEvent -> ManagedPtr PadEvent
toManagedPtr (PadEvent ManagedPtr PadEvent
p) = ManagedPtr PadEvent
p

foreign import ccall "gdk_pad_event_get_type"
    c_gdk_pad_event_get_type :: IO B.Types.GType

instance B.Types.TypedObject PadEvent where
    glibType :: IO GType
glibType = IO GType
c_gdk_pad_event_get_type

-- | Type class for types which can be safely cast to `PadEvent`, for instance with `toPadEvent`.
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf PadEvent o) => IsPadEvent o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf PadEvent o) => IsPadEvent o

instance O.HasParentTypes PadEvent
type instance O.ParentTypes PadEvent = '[Gdk.Event.Event]

-- | Cast to `PadEvent`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toPadEvent :: (MIO.MonadIO m, IsPadEvent o) => o -> m PadEvent
toPadEvent :: forall (m :: * -> *) o.
(MonadIO m, IsPadEvent o) =>
o -> m PadEvent
toPadEvent = IO PadEvent -> m PadEvent
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PadEvent -> m PadEvent)
-> (o -> IO PadEvent) -> o -> m PadEvent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr PadEvent -> PadEvent) -> o -> IO PadEvent
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr PadEvent -> PadEvent
PadEvent

--- XXX Missing getter and/or setter, so no GValue instance could be generated.
#if defined(ENABLE_OVERLOADING)
type family ResolvePadEventMethod (t :: Symbol) (o :: *) :: * where
    ResolvePadEventMethod "ref" o = Gdk.Event.EventRefMethodInfo
    ResolvePadEventMethod "triggersContextMenu" o = Gdk.Event.EventTriggersContextMenuMethodInfo
    ResolvePadEventMethod "unref" o = Gdk.Event.EventUnrefMethodInfo
    ResolvePadEventMethod "getAxes" o = Gdk.Event.EventGetAxesMethodInfo
    ResolvePadEventMethod "getAxis" o = Gdk.Event.EventGetAxisMethodInfo
    ResolvePadEventMethod "getAxisValue" o = PadEventGetAxisValueMethodInfo
    ResolvePadEventMethod "getButton" o = PadEventGetButtonMethodInfo
    ResolvePadEventMethod "getDevice" o = Gdk.Event.EventGetDeviceMethodInfo
    ResolvePadEventMethod "getDeviceTool" o = Gdk.Event.EventGetDeviceToolMethodInfo
    ResolvePadEventMethod "getDisplay" o = Gdk.Event.EventGetDisplayMethodInfo
    ResolvePadEventMethod "getEventSequence" o = Gdk.Event.EventGetEventSequenceMethodInfo
    ResolvePadEventMethod "getEventType" o = Gdk.Event.EventGetEventTypeMethodInfo
    ResolvePadEventMethod "getGroupMode" o = PadEventGetGroupModeMethodInfo
    ResolvePadEventMethod "getHistory" o = Gdk.Event.EventGetHistoryMethodInfo
    ResolvePadEventMethod "getModifierState" o = Gdk.Event.EventGetModifierStateMethodInfo
    ResolvePadEventMethod "getPointerEmulated" o = Gdk.Event.EventGetPointerEmulatedMethodInfo
    ResolvePadEventMethod "getPosition" o = Gdk.Event.EventGetPositionMethodInfo
    ResolvePadEventMethod "getSeat" o = Gdk.Event.EventGetSeatMethodInfo
    ResolvePadEventMethod "getSurface" o = Gdk.Event.EventGetSurfaceMethodInfo
    ResolvePadEventMethod "getTime" o = Gdk.Event.EventGetTimeMethodInfo
    ResolvePadEventMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolvePadEventMethod t PadEvent, O.OverloadedMethod info PadEvent p, R.HasField t PadEvent p) => R.HasField t PadEvent p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolvePadEventMethod t PadEvent, O.OverloadedMethodInfo info PadEvent) => OL.IsLabel t (O.MethodProxy info PadEvent) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr PadEvent where
    boxedPtrCopy :: PadEvent -> IO PadEvent
boxedPtrCopy = PadEvent -> IO PadEvent
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: PadEvent -> IO ()
boxedPtrFree = \PadEvent
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


-- method PadEvent::get_axis_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "event"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "PadEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pad strip or ring event"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for the axis index"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for the axis value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pad_event_get_axis_value" gdk_pad_event_get_axis_value :: 
    Ptr PadEvent ->                         -- event : TInterface (Name {namespace = "Gdk", name = "PadEvent"})
    Ptr Word32 ->                           -- index : TBasicType TUInt
    Ptr CDouble ->                          -- value : TBasicType TDouble
    IO ()

-- | Extracts the information from a pad strip or ring event.
padEventGetAxisValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsPadEvent a) =>
    a
    -- ^ /@event@/: a pad strip or ring event
    -> m ((Word32, Double))
padEventGetAxisValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPadEvent a) =>
a -> m (Word32, Double)
padEventGetAxisValue a
event = IO (Word32, Double) -> m (Word32, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word32, Double) -> m (Word32, Double))
-> IO (Word32, Double) -> m (Word32, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PadEvent
event' <- a -> IO (Ptr PadEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
event
    Ptr Word32
index <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr CDouble
value <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr PadEvent -> Ptr Word32 -> Ptr CDouble -> IO ()
gdk_pad_event_get_axis_value Ptr PadEvent
event' Ptr Word32
index Ptr CDouble
value
    Word32
index' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
index
    CDouble
value' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
value
    let value'' :: Double
value'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
event
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
index
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
value
    (Word32, Double) -> IO (Word32, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
index', Double
value'')

#if defined(ENABLE_OVERLOADING)
data PadEventGetAxisValueMethodInfo
instance (signature ~ (m ((Word32, Double))), MonadIO m, IsPadEvent a) => O.OverloadedMethod PadEventGetAxisValueMethodInfo a signature where
    overloadedMethod = padEventGetAxisValue

instance O.OverloadedMethodInfo PadEventGetAxisValueMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.PadEvent.padEventGetAxisValue",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-PadEvent.html#v:padEventGetAxisValue"
        }


#endif

-- method PadEvent::get_button
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "event"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "PadEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pad button event" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pad_event_get_button" gdk_pad_event_get_button :: 
    Ptr PadEvent ->                         -- event : TInterface (Name {namespace = "Gdk", name = "PadEvent"})
    IO Word32

-- | Extracts information about the pressed button from
-- a pad event.
padEventGetButton ::
    (B.CallStack.HasCallStack, MonadIO m, IsPadEvent a) =>
    a
    -- ^ /@event@/: a pad button event
    -> m Word32
    -- ^ __Returns:__ the button of /@event@/
padEventGetButton :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPadEvent a) =>
a -> m Word32
padEventGetButton a
event = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PadEvent
event' <- a -> IO (Ptr PadEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
event
    Word32
result <- Ptr PadEvent -> IO Word32
gdk_pad_event_get_button Ptr PadEvent
event'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
event
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data PadEventGetButtonMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsPadEvent a) => O.OverloadedMethod PadEventGetButtonMethodInfo a signature where
    overloadedMethod = padEventGetButton

instance O.OverloadedMethodInfo PadEventGetButtonMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.PadEvent.padEventGetButton",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-PadEvent.html#v:padEventGetButton"
        }


#endif

-- method PadEvent::get_group_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "event"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "PadEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pad event" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "mode"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the mode"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_pad_event_get_group_mode" gdk_pad_event_get_group_mode :: 
    Ptr PadEvent ->                         -- event : TInterface (Name {namespace = "Gdk", name = "PadEvent"})
    Ptr Word32 ->                           -- group : TBasicType TUInt
    Ptr Word32 ->                           -- mode : TBasicType TUInt
    IO ()

-- | Extracts group and mode information from a pad event.
padEventGetGroupMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsPadEvent a) =>
    a
    -- ^ /@event@/: a pad event
    -> m ((Word32, Word32))
padEventGetGroupMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPadEvent a) =>
a -> m (Word32, Word32)
padEventGetGroupMode a
event = IO (Word32, Word32) -> m (Word32, Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word32, Word32) -> m (Word32, Word32))
-> IO (Word32, Word32) -> m (Word32, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PadEvent
event' <- a -> IO (Ptr PadEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
event
    Ptr Word32
group <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr Word32
mode <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr PadEvent -> Ptr Word32 -> Ptr Word32 -> IO ()
gdk_pad_event_get_group_mode Ptr PadEvent
event' Ptr Word32
group Ptr Word32
mode
    Word32
group' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
group
    Word32
mode' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
mode
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
event
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
group
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
mode
    (Word32, Word32) -> IO (Word32, Word32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
group', Word32
mode')

#if defined(ENABLE_OVERLOADING)
data PadEventGetGroupModeMethodInfo
instance (signature ~ (m ((Word32, Word32))), MonadIO m, IsPadEvent a) => O.OverloadedMethod PadEventGetGroupModeMethodInfo a signature where
    overloadedMethod = padEventGetGroupMode

instance O.OverloadedMethodInfo PadEventGetGroupModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gdk.Objects.PadEvent.padEventGetGroupMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gdk-4.0.3/docs/GI-Gdk-Objects-PadEvent.html#v:padEventGetGroupMode"
        }


#endif