{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Gdk.Objects.MotionEvent
    ( 

-- * Exported types
    MotionEvent(..)                         ,
    IsMotionEvent                           ,
    toMotionEvent                           ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveMotionEventMethod                ,
#endif


-- ** getHistory #method:getHistory#

#if defined(ENABLE_OVERLOADING)
    MotionEventGetHistoryMethodInfo         ,
#endif
    motionEventGetHistory                   ,




    ) 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.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 {-# SOURCE #-} qualified GI.Gdk.Objects.Event as Gdk.Event
import {-# SOURCE #-} qualified GI.Gdk.Structs.TimeCoord as Gdk.TimeCoord

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

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

foreign import ccall "gdk_motion_event_get_type"
    c_gdk_motion_event_get_type :: IO B.Types.GType

instance B.Types.TypedObject MotionEvent where
    glibType :: IO GType
glibType = IO GType
c_gdk_motion_event_get_type

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveMotionEventMethod (t :: Symbol) (o :: *) :: * where
    ResolveMotionEventMethod "ref" o = Gdk.Event.EventRefMethodInfo
    ResolveMotionEventMethod "triggersContextMenu" o = Gdk.Event.EventTriggersContextMenuMethodInfo
    ResolveMotionEventMethod "unref" o = Gdk.Event.EventUnrefMethodInfo
    ResolveMotionEventMethod "getAxes" o = Gdk.Event.EventGetAxesMethodInfo
    ResolveMotionEventMethod "getAxis" o = Gdk.Event.EventGetAxisMethodInfo
    ResolveMotionEventMethod "getDevice" o = Gdk.Event.EventGetDeviceMethodInfo
    ResolveMotionEventMethod "getDeviceTool" o = Gdk.Event.EventGetDeviceToolMethodInfo
    ResolveMotionEventMethod "getDisplay" o = Gdk.Event.EventGetDisplayMethodInfo
    ResolveMotionEventMethod "getEventSequence" o = Gdk.Event.EventGetEventSequenceMethodInfo
    ResolveMotionEventMethod "getEventType" o = Gdk.Event.EventGetEventTypeMethodInfo
    ResolveMotionEventMethod "getHistory" o = MotionEventGetHistoryMethodInfo
    ResolveMotionEventMethod "getModifierState" o = Gdk.Event.EventGetModifierStateMethodInfo
    ResolveMotionEventMethod "getPointerEmulated" o = Gdk.Event.EventGetPointerEmulatedMethodInfo
    ResolveMotionEventMethod "getPosition" o = Gdk.Event.EventGetPositionMethodInfo
    ResolveMotionEventMethod "getSourceDevice" o = Gdk.Event.EventGetSourceDeviceMethodInfo
    ResolveMotionEventMethod "getSurface" o = Gdk.Event.EventGetSurfaceMethodInfo
    ResolveMotionEventMethod "getTime" o = Gdk.Event.EventGetTimeMethodInfo
    ResolveMotionEventMethod l o = O.MethodResolutionFailed l o

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

#endif

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


-- method MotionEvent::get_history
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "event"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "MotionEvent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a motion #GdkEvent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_n_coords"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Return location for the length of the returned array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "out_n_coords"
--              , argType = TBasicType TUInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "Return location for the length of the returned array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just
--               (TCArray
--                  False
--                  (-1)
--                  1
--                  (TInterface Name { namespace = "Gdk" , name = "TimeCoord" }))
-- throws : False
-- Skip return : False

foreign import ccall "gdk_motion_event_get_history" gdk_motion_event_get_history :: 
    Ptr MotionEvent ->                      -- event : TInterface (Name {namespace = "Gdk", name = "MotionEvent"})
    Ptr Word32 ->                           -- out_n_coords : TBasicType TUInt
    IO (Ptr Gdk.TimeCoord.TimeCoord)

-- | Retrieves the history of the /@event@/ motion, as a list of time and
-- coordinates.
motionEventGetHistory ::
    (B.CallStack.HasCallStack, MonadIO m, IsMotionEvent a) =>
    a
    -- ^ /@event@/: a motion t'GI.Gdk.Objects.Event.Event'
    -> m (Maybe [Gdk.TimeCoord.TimeCoord])
    -- ^ __Returns:__ an
    --   array of time and coordinates
motionEventGetHistory :: a -> m (Maybe [TimeCoord])
motionEventGetHistory a
event = IO (Maybe [TimeCoord]) -> m (Maybe [TimeCoord])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [TimeCoord]) -> m (Maybe [TimeCoord]))
-> IO (Maybe [TimeCoord]) -> m (Maybe [TimeCoord])
forall a b. (a -> b) -> a -> b
$ do
    Ptr MotionEvent
event' <- a -> IO (Ptr MotionEvent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
event
    Ptr Word32
outNCoords <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr TimeCoord
result <- Ptr MotionEvent -> Ptr Word32 -> IO (Ptr TimeCoord)
gdk_motion_event_get_history Ptr MotionEvent
event' Ptr Word32
outNCoords
    Word32
outNCoords' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
outNCoords
    Maybe [TimeCoord]
maybeResult <- Ptr TimeCoord
-> (Ptr TimeCoord -> IO [TimeCoord]) -> IO (Maybe [TimeCoord])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TimeCoord
result ((Ptr TimeCoord -> IO [TimeCoord]) -> IO (Maybe [TimeCoord]))
-> (Ptr TimeCoord -> IO [TimeCoord]) -> IO (Maybe [TimeCoord])
forall a b. (a -> b) -> a -> b
$ \Ptr TimeCoord
result' -> do
        [Ptr TimeCoord]
result'' <- (Int -> Word32 -> Ptr TimeCoord -> IO [Ptr TimeCoord]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength Int
1032 Word32
outNCoords') Ptr TimeCoord
result'
        [TimeCoord]
result''' <- (Ptr TimeCoord -> IO TimeCoord)
-> [Ptr TimeCoord] -> IO [TimeCoord]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr TimeCoord -> TimeCoord)
-> Ptr TimeCoord -> IO TimeCoord
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TimeCoord -> TimeCoord
Gdk.TimeCoord.TimeCoord) [Ptr TimeCoord]
result''
        Ptr TimeCoord -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr TimeCoord
result'
        [TimeCoord] -> IO [TimeCoord]
forall (m :: * -> *) a. Monad m => a -> m a
return [TimeCoord]
result'''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
event
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
outNCoords
    Maybe [TimeCoord] -> IO (Maybe [TimeCoord])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [TimeCoord]
maybeResult

#if defined(ENABLE_OVERLOADING)
data MotionEventGetHistoryMethodInfo
instance (signature ~ (m (Maybe [Gdk.TimeCoord.TimeCoord])), MonadIO m, IsMotionEvent a) => O.MethodInfo MotionEventGetHistoryMethodInfo a signature where
    overloadedMethod = motionEventGetHistory

#endif