{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Contains the fields which are common to all event structs.
-- Any event pointer can safely be cast to a pointer to a t'GI.Gdk.Structs.EventAny.EventAny' to
-- access these fields.

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

module GI.Gdk.Structs.EventAny
    ( 

-- * Exported types
    EventAny(..)                            ,
    newZeroEventAny                         ,
    noEventAny                              ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveEventAnyMethod                   ,
#endif




 -- * Properties
-- ** sendEvent #attr:sendEvent#
-- | 'P.True' if the event was sent explicitly.

#if defined(ENABLE_OVERLOADING)
    eventAny_sendEvent                      ,
#endif
    getEventAnySendEvent                    ,
    setEventAnySendEvent                    ,


-- ** type #attr:type#
-- | the type of the event.

#if defined(ENABLE_OVERLOADING)
    eventAny_type                           ,
#endif
    getEventAnyType                         ,
    setEventAnyType                         ,


-- ** window #attr:window#
-- | the window which received the event.

    clearEventAnyWindow                     ,
#if defined(ENABLE_OVERLOADING)
    eventAny_window                         ,
#endif
    getEventAnyWindow                       ,
    setEventAnyWindow                       ,




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

-- | Memory-managed wrapper type.
newtype EventAny = EventAny (ManagedPtr EventAny)
    deriving (EventAny -> EventAny -> Bool
(EventAny -> EventAny -> Bool)
-> (EventAny -> EventAny -> Bool) -> Eq EventAny
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventAny -> EventAny -> Bool
$c/= :: EventAny -> EventAny -> Bool
== :: EventAny -> EventAny -> Bool
$c== :: EventAny -> EventAny -> Bool
Eq)
instance WrappedPtr EventAny where
    wrappedPtrCalloc :: IO (Ptr EventAny)
wrappedPtrCalloc = Int -> IO (Ptr EventAny)
forall a. Int -> IO (Ptr a)
callocBytes 24
    wrappedPtrCopy :: EventAny -> IO EventAny
wrappedPtrCopy = \p :: EventAny
p -> EventAny -> (Ptr EventAny -> IO EventAny) -> IO EventAny
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventAny
p (Int -> Ptr EventAny -> IO (Ptr EventAny)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 24 (Ptr EventAny -> IO (Ptr EventAny))
-> (Ptr EventAny -> IO EventAny) -> Ptr EventAny -> IO EventAny
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventAny -> EventAny) -> Ptr EventAny -> IO EventAny
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventAny -> EventAny
EventAny)
    wrappedPtrFree :: Maybe (GDestroyNotify EventAny)
wrappedPtrFree = GDestroyNotify EventAny -> Maybe (GDestroyNotify EventAny)
forall a. a -> Maybe a
Just GDestroyNotify EventAny
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `EventAny` struct initialized to zero.
newZeroEventAny :: MonadIO m => m EventAny
newZeroEventAny :: m EventAny
newZeroEventAny = IO EventAny -> m EventAny
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventAny -> m EventAny) -> IO EventAny -> m EventAny
forall a b. (a -> b) -> a -> b
$ IO (Ptr EventAny)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr EventAny) -> (Ptr EventAny -> IO EventAny) -> IO EventAny
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventAny -> EventAny) -> Ptr EventAny -> IO EventAny
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventAny -> EventAny
EventAny

instance tag ~ 'AttrSet => Constructible EventAny tag where
    new :: (ManagedPtr EventAny -> EventAny)
-> [AttrOp EventAny tag] -> m EventAny
new _ attrs :: [AttrOp EventAny tag]
attrs = do
        EventAny
o <- m EventAny
forall (m :: * -> *). MonadIO m => m EventAny
newZeroEventAny
        EventAny -> [AttrOp EventAny 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set EventAny
o [AttrOp EventAny tag]
[AttrOp EventAny 'AttrSet]
attrs
        EventAny -> m EventAny
forall (m :: * -> *) a. Monad m => a -> m a
return EventAny
o


-- | A convenience alias for `Nothing` :: `Maybe` `EventAny`.
noEventAny :: Maybe EventAny
noEventAny :: Maybe EventAny
noEventAny = Maybe EventAny
forall a. Maybe a
Nothing

-- | Get the value of the “@type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventAny #type
-- @
getEventAnyType :: MonadIO m => EventAny -> m Gdk.Enums.EventType
getEventAnyType :: EventAny -> m EventType
getEventAnyType s :: EventAny
s = IO EventType -> m EventType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventType -> m EventType) -> IO EventType -> m EventType
forall a b. (a -> b) -> a -> b
$ EventAny -> (Ptr EventAny -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventAny
s ((Ptr EventAny -> IO EventType) -> IO EventType)
-> (Ptr EventAny -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventAny
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventAny
ptr Ptr EventAny -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO CInt
    let val' :: EventType
val' = (Int -> EventType
forall a. Enum a => Int -> a
toEnum (Int -> EventType) -> (CInt -> Int) -> CInt -> EventType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
val
    EventType -> IO EventType
forall (m :: * -> *) a. Monad m => a -> m a
return EventType
val'

-- | Set the value of the “@type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventAny [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventAnyType :: MonadIO m => EventAny -> Gdk.Enums.EventType -> m ()
setEventAnyType :: EventAny -> EventType -> m ()
setEventAnyType s :: EventAny
s val :: EventType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventAny -> (Ptr EventAny -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventAny
s ((Ptr EventAny -> IO ()) -> IO ())
-> (Ptr EventAny -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventAny
ptr -> do
    let val' :: CInt
val' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EventType -> Int) -> EventType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventType -> Int
forall a. Enum a => a -> Int
fromEnum) EventType
val
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventAny
ptr Ptr EventAny -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CInt
val' :: CInt)

#if defined(ENABLE_OVERLOADING)
data EventAnyTypeFieldInfo
instance AttrInfo EventAnyTypeFieldInfo where
    type AttrBaseTypeConstraint EventAnyTypeFieldInfo = (~) EventAny
    type AttrAllowedOps EventAnyTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventAnyTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrTransferTypeConstraint EventAnyTypeFieldInfo = (~)Gdk.Enums.EventType
    type AttrTransferType EventAnyTypeFieldInfo = Gdk.Enums.EventType
    type AttrGetType EventAnyTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventAnyTypeFieldInfo = "type"
    type AttrOrigin EventAnyTypeFieldInfo = EventAny
    attrGet = getEventAnyType
    attrSet = setEventAnyType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventAny_type :: AttrLabelProxy "type"
eventAny_type = AttrLabelProxy

#endif


-- | Get the value of the “@window@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventAny #window
-- @
getEventAnyWindow :: MonadIO m => EventAny -> m (Maybe Gdk.Window.Window)
getEventAnyWindow :: EventAny -> m (Maybe Window)
getEventAnyWindow s :: EventAny
s = IO (Maybe Window) -> m (Maybe Window)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ EventAny
-> (Ptr EventAny -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventAny
s ((Ptr EventAny -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventAny -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventAny
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventAny
ptr Ptr EventAny -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO (Ptr Gdk.Window.Window)
    Maybe Window
result <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Window
val ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Window
val' -> do
        Window
val'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
val'
        Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
val''
    Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
result

-- | Set the value of the “@window@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventAny [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventAnyWindow :: MonadIO m => EventAny -> Ptr Gdk.Window.Window -> m ()
setEventAnyWindow :: EventAny -> Ptr Window -> m ()
setEventAnyWindow s :: EventAny
s val :: Ptr Window
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventAny -> (Ptr EventAny -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventAny
s ((Ptr EventAny -> IO ()) -> IO ())
-> (Ptr EventAny -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventAny
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventAny
ptr Ptr EventAny -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Window
val :: Ptr Gdk.Window.Window)

-- | Set the value of the “@window@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #window
-- @
clearEventAnyWindow :: MonadIO m => EventAny -> m ()
clearEventAnyWindow :: EventAny -> m ()
clearEventAnyWindow s :: EventAny
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventAny -> (Ptr EventAny -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventAny
s ((Ptr EventAny -> IO ()) -> IO ())
-> (Ptr EventAny -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventAny
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventAny
ptr Ptr EventAny -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Window
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Window.Window)

#if defined(ENABLE_OVERLOADING)
data EventAnyWindowFieldInfo
instance AttrInfo EventAnyWindowFieldInfo where
    type AttrBaseTypeConstraint EventAnyWindowFieldInfo = (~) EventAny
    type AttrAllowedOps EventAnyWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventAnyWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventAnyWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventAnyWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventAnyWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventAnyWindowFieldInfo = "window"
    type AttrOrigin EventAnyWindowFieldInfo = EventAny
    attrGet = getEventAnyWindow
    attrSet = setEventAnyWindow
    attrConstruct = undefined
    attrClear = clearEventAnyWindow
    attrTransfer _ v = do
        return v

eventAny_window :: AttrLabelProxy "window"
eventAny_window = AttrLabelProxy

#endif


-- | Get the value of the “@send_event@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventAny #sendEvent
-- @
getEventAnySendEvent :: MonadIO m => EventAny -> m Int8
getEventAnySendEvent :: EventAny -> m Int8
getEventAnySendEvent s :: EventAny
s = IO Int8 -> m Int8
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int8 -> m Int8) -> IO Int8 -> m Int8
forall a b. (a -> b) -> a -> b
$ EventAny -> (Ptr EventAny -> IO Int8) -> IO Int8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventAny
s ((Ptr EventAny -> IO Int8) -> IO Int8)
-> (Ptr EventAny -> IO Int8) -> IO Int8
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventAny
ptr -> do
    Int8
val <- Ptr Int8 -> IO Int8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventAny
ptr Ptr EventAny -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO Int8
    Int8 -> IO Int8
forall (m :: * -> *) a. Monad m => a -> m a
return Int8
val

-- | Set the value of the “@send_event@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventAny [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventAnySendEvent :: MonadIO m => EventAny -> Int8 -> m ()
setEventAnySendEvent :: EventAny -> Int8 -> m ()
setEventAnySendEvent s :: EventAny
s val :: Int8
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventAny -> (Ptr EventAny -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventAny
s ((Ptr EventAny -> IO ()) -> IO ())
-> (Ptr EventAny -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventAny
ptr -> do
    Ptr Int8 -> Int8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventAny
ptr Ptr EventAny -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Int8
val :: Int8)

#if defined(ENABLE_OVERLOADING)
data EventAnySendEventFieldInfo
instance AttrInfo EventAnySendEventFieldInfo where
    type AttrBaseTypeConstraint EventAnySendEventFieldInfo = (~) EventAny
    type AttrAllowedOps EventAnySendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventAnySendEventFieldInfo = (~) Int8
    type AttrTransferTypeConstraint EventAnySendEventFieldInfo = (~)Int8
    type AttrTransferType EventAnySendEventFieldInfo = Int8
    type AttrGetType EventAnySendEventFieldInfo = Int8
    type AttrLabel EventAnySendEventFieldInfo = "send_event"
    type AttrOrigin EventAnySendEventFieldInfo = EventAny
    attrGet = getEventAnySendEvent
    attrSet = setEventAnySendEvent
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventAny_sendEvent :: AttrLabelProxy "sendEvent"
eventAny_sendEvent = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventAny
type instance O.AttributeList EventAny = EventAnyAttributeList
type EventAnyAttributeList = ('[ '("type", EventAnyTypeFieldInfo), '("window", EventAnyWindowFieldInfo), '("sendEvent", EventAnySendEventFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveEventAnyMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventAnyMethod l o = O.MethodResolutionFailed l o

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

#endif