{- | Copyright : Will Thompson, Iñaki García Etxebarria and Jonas Platte License : LGPL-2.1 Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc) Generated when the state of a toplevel window changes. -} #define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \ && !defined(__HADDOCK_VERSION__)) module GI.Gdk.Structs.EventWindowState ( -- * Exported types EventWindowState(..) , newZeroEventWindowState , noEventWindowState , -- * Properties -- ** changedMask #attr:changedMask# {- | mask specifying what flags have changed. -} #if ENABLE_OVERLOADING eventWindowState_changedMask , #endif getEventWindowStateChangedMask , setEventWindowStateChangedMask , -- ** newWindowState #attr:newWindowState# {- | the new window state, a combination of 'GI.Gdk.Flags.WindowState' bits. -} #if ENABLE_OVERLOADING eventWindowState_newWindowState , #endif getEventWindowStateNewWindowState , setEventWindowStateNewWindowState , -- ** sendEvent #attr:sendEvent# {- | 'True' if the event was sent explicitly. -} #if ENABLE_OVERLOADING eventWindowState_sendEvent , #endif getEventWindowStateSendEvent , setEventWindowStateSendEvent , -- ** type #attr:type# {- | the type of the event ('GI.Gdk.Enums.EventTypeWindowState'). -} #if ENABLE_OVERLOADING eventWindowState_type , #endif getEventWindowStateType , setEventWindowStateType , -- ** window #attr:window# {- | the window which received the event. -} clearEventWindowStateWindow , #if ENABLE_OVERLOADING eventWindowState_window , #endif getEventWindowStateWindow , setEventWindowStateWindow , ) 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.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.Flags as Gdk.Flags import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window -- | Memory-managed wrapper type. newtype EventWindowState = EventWindowState (ManagedPtr EventWindowState) instance WrappedPtr EventWindowState where wrappedPtrCalloc = callocBytes 32 wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 32 >=> wrapPtr EventWindowState) wrappedPtrFree = Just ptr_to_g_free -- | Construct a `EventWindowState` struct initialized to zero. newZeroEventWindowState :: MonadIO m => m EventWindowState newZeroEventWindowState = liftIO $ wrappedPtrCalloc >>= wrapPtr EventWindowState instance tag ~ 'AttrSet => Constructible EventWindowState tag where new _ attrs = do o <- newZeroEventWindowState GI.Attributes.set o attrs return o -- | A convenience alias for `Nothing` :: `Maybe` `EventWindowState`. noEventWindowState :: Maybe EventWindowState noEventWindowState = Nothing {- | Get the value of the “@type@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventWindowState #type @ -} getEventWindowStateType :: MonadIO m => EventWindowState -> m Gdk.Enums.EventType getEventWindowStateType s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 0) :: IO CInt let val' = (toEnum . fromIntegral) val return val' {- | Set the value of the “@type@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventWindowState [ #type 'Data.GI.Base.Attributes.:=' value ] @ -} setEventWindowStateType :: MonadIO m => EventWindowState -> Gdk.Enums.EventType -> m () setEventWindowStateType s val = liftIO $ withManagedPtr s $ \ptr -> do let val' = (fromIntegral . fromEnum) val poke (ptr `plusPtr` 0) (val' :: CInt) #if ENABLE_OVERLOADING data EventWindowStateTypeFieldInfo instance AttrInfo EventWindowStateTypeFieldInfo where type AttrAllowedOps EventWindowStateTypeFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventWindowStateTypeFieldInfo = (~) Gdk.Enums.EventType type AttrBaseTypeConstraint EventWindowStateTypeFieldInfo = (~) EventWindowState type AttrGetType EventWindowStateTypeFieldInfo = Gdk.Enums.EventType type AttrLabel EventWindowStateTypeFieldInfo = "type" type AttrOrigin EventWindowStateTypeFieldInfo = EventWindowState attrGet _ = getEventWindowStateType attrSet _ = setEventWindowStateType attrConstruct = undefined attrClear _ = undefined eventWindowState_type :: AttrLabelProxy "type" eventWindowState_type = AttrLabelProxy #endif {- | Get the value of the “@window@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventWindowState #window @ -} getEventWindowStateWindow :: MonadIO m => EventWindowState -> m (Maybe Gdk.Window.Window) getEventWindowStateWindow s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 8) :: IO (Ptr Gdk.Window.Window) result <- SP.convertIfNonNull val $ \val' -> do val'' <- (newObject Gdk.Window.Window) val' return val'' return result {- | Set the value of the “@window@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventWindowState [ #window 'Data.GI.Base.Attributes.:=' value ] @ -} setEventWindowStateWindow :: MonadIO m => EventWindowState -> Ptr Gdk.Window.Window -> m () setEventWindowStateWindow s val = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window) {- | Set the value of the “@window@” field to `Nothing`. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.clear' #window @ -} clearEventWindowStateWindow :: MonadIO m => EventWindowState -> m () clearEventWindowStateWindow s = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window) #if ENABLE_OVERLOADING data EventWindowStateWindowFieldInfo instance AttrInfo EventWindowStateWindowFieldInfo where type AttrAllowedOps EventWindowStateWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear] type AttrSetTypeConstraint EventWindowStateWindowFieldInfo = (~) (Ptr Gdk.Window.Window) type AttrBaseTypeConstraint EventWindowStateWindowFieldInfo = (~) EventWindowState type AttrGetType EventWindowStateWindowFieldInfo = Maybe Gdk.Window.Window type AttrLabel EventWindowStateWindowFieldInfo = "window" type AttrOrigin EventWindowStateWindowFieldInfo = EventWindowState attrGet _ = getEventWindowStateWindow attrSet _ = setEventWindowStateWindow attrConstruct = undefined attrClear _ = clearEventWindowStateWindow eventWindowState_window :: AttrLabelProxy "window" eventWindowState_window = AttrLabelProxy #endif {- | Get the value of the “@send_event@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventWindowState #sendEvent @ -} getEventWindowStateSendEvent :: MonadIO m => EventWindowState -> m Int8 getEventWindowStateSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 16) :: IO Int8 return val {- | Set the value of the “@send_event@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventWindowState [ #sendEvent 'Data.GI.Base.Attributes.:=' value ] @ -} setEventWindowStateSendEvent :: MonadIO m => EventWindowState -> Int8 -> m () setEventWindowStateSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 16) (val :: Int8) #if ENABLE_OVERLOADING data EventWindowStateSendEventFieldInfo instance AttrInfo EventWindowStateSendEventFieldInfo where type AttrAllowedOps EventWindowStateSendEventFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventWindowStateSendEventFieldInfo = (~) Int8 type AttrBaseTypeConstraint EventWindowStateSendEventFieldInfo = (~) EventWindowState type AttrGetType EventWindowStateSendEventFieldInfo = Int8 type AttrLabel EventWindowStateSendEventFieldInfo = "send_event" type AttrOrigin EventWindowStateSendEventFieldInfo = EventWindowState attrGet _ = getEventWindowStateSendEvent attrSet _ = setEventWindowStateSendEvent attrConstruct = undefined attrClear _ = undefined eventWindowState_sendEvent :: AttrLabelProxy "sendEvent" eventWindowState_sendEvent = AttrLabelProxy #endif {- | Get the value of the “@changed_mask@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventWindowState #changedMask @ -} getEventWindowStateChangedMask :: MonadIO m => EventWindowState -> m [Gdk.Flags.WindowState] getEventWindowStateChangedMask s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 20) :: IO CUInt let val' = wordToGFlags val return val' {- | Set the value of the “@changed_mask@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventWindowState [ #changedMask 'Data.GI.Base.Attributes.:=' value ] @ -} setEventWindowStateChangedMask :: MonadIO m => EventWindowState -> [Gdk.Flags.WindowState] -> m () setEventWindowStateChangedMask s val = liftIO $ withManagedPtr s $ \ptr -> do let val' = gflagsToWord val poke (ptr `plusPtr` 20) (val' :: CUInt) #if ENABLE_OVERLOADING data EventWindowStateChangedMaskFieldInfo instance AttrInfo EventWindowStateChangedMaskFieldInfo where type AttrAllowedOps EventWindowStateChangedMaskFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventWindowStateChangedMaskFieldInfo = (~) [Gdk.Flags.WindowState] type AttrBaseTypeConstraint EventWindowStateChangedMaskFieldInfo = (~) EventWindowState type AttrGetType EventWindowStateChangedMaskFieldInfo = [Gdk.Flags.WindowState] type AttrLabel EventWindowStateChangedMaskFieldInfo = "changed_mask" type AttrOrigin EventWindowStateChangedMaskFieldInfo = EventWindowState attrGet _ = getEventWindowStateChangedMask attrSet _ = setEventWindowStateChangedMask attrConstruct = undefined attrClear _ = undefined eventWindowState_changedMask :: AttrLabelProxy "changedMask" eventWindowState_changedMask = AttrLabelProxy #endif {- | Get the value of the “@new_window_state@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventWindowState #newWindowState @ -} getEventWindowStateNewWindowState :: MonadIO m => EventWindowState -> m [Gdk.Flags.WindowState] getEventWindowStateNewWindowState s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 24) :: IO CUInt let val' = wordToGFlags val return val' {- | Set the value of the “@new_window_state@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventWindowState [ #newWindowState 'Data.GI.Base.Attributes.:=' value ] @ -} setEventWindowStateNewWindowState :: MonadIO m => EventWindowState -> [Gdk.Flags.WindowState] -> m () setEventWindowStateNewWindowState s val = liftIO $ withManagedPtr s $ \ptr -> do let val' = gflagsToWord val poke (ptr `plusPtr` 24) (val' :: CUInt) #if ENABLE_OVERLOADING data EventWindowStateNewWindowStateFieldInfo instance AttrInfo EventWindowStateNewWindowStateFieldInfo where type AttrAllowedOps EventWindowStateNewWindowStateFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventWindowStateNewWindowStateFieldInfo = (~) [Gdk.Flags.WindowState] type AttrBaseTypeConstraint EventWindowStateNewWindowStateFieldInfo = (~) EventWindowState type AttrGetType EventWindowStateNewWindowStateFieldInfo = [Gdk.Flags.WindowState] type AttrLabel EventWindowStateNewWindowStateFieldInfo = "new_window_state" type AttrOrigin EventWindowStateNewWindowStateFieldInfo = EventWindowState attrGet _ = getEventWindowStateNewWindowState attrSet _ = setEventWindowStateNewWindowState attrConstruct = undefined attrClear _ = undefined eventWindowState_newWindowState :: AttrLabelProxy "newWindowState" eventWindowState_newWindowState = AttrLabelProxy #endif #if ENABLE_OVERLOADING instance O.HasAttributeList EventWindowState type instance O.AttributeList EventWindowState = EventWindowStateAttributeList type EventWindowStateAttributeList = ('[ '("type", EventWindowStateTypeFieldInfo), '("window", EventWindowStateWindowFieldInfo), '("sendEvent", EventWindowStateSendEventFieldInfo), '("changedMask", EventWindowStateChangedMaskFieldInfo), '("newWindowState", EventWindowStateNewWindowStateFieldInfo)] :: [(Symbol, *)]) #endif #if ENABLE_OVERLOADING type family ResolveEventWindowStateMethod (t :: Symbol) (o :: *) :: * where ResolveEventWindowStateMethod l o = O.MethodResolutionFailed l o instance (info ~ ResolveEventWindowStateMethod t EventWindowState, O.MethodInfo info EventWindowState p) => OL.IsLabel t (EventWindowState -> p) where #if MIN_VERSION_base(4,10,0) fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info) #else fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info) #endif #endif