{- | 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 a window size or position has changed. -} #define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \ && !defined(__HADDOCK_VERSION__)) module GI.Gdk.Structs.EventConfigure ( -- * Exported types EventConfigure(..) , newZeroEventConfigure , noEventConfigure , -- * Properties -- ** height #attr:height# {- | the new height of the window. -} #if ENABLE_OVERLOADING eventConfigure_height , #endif getEventConfigureHeight , setEventConfigureHeight , -- ** sendEvent #attr:sendEvent# {- | 'True' if the event was sent explicitly. -} #if ENABLE_OVERLOADING eventConfigure_sendEvent , #endif getEventConfigureSendEvent , setEventConfigureSendEvent , -- ** type #attr:type# {- | the type of the event ('GI.Gdk.Enums.EventTypeConfigure'). -} #if ENABLE_OVERLOADING eventConfigure_type , #endif getEventConfigureType , setEventConfigureType , -- ** width #attr:width# {- | the new width of the window. -} #if ENABLE_OVERLOADING eventConfigure_width , #endif getEventConfigureWidth , setEventConfigureWidth , -- ** window #attr:window# {- | the window which received the event. -} clearEventConfigureWindow , #if ENABLE_OVERLOADING eventConfigure_window , #endif getEventConfigureWindow , setEventConfigureWindow , -- ** x #attr:x# {- | the new x coordinate of the window, relative to its parent. -} #if ENABLE_OVERLOADING eventConfigure_x , #endif getEventConfigureX , setEventConfigureX , -- ** y #attr:y# {- | the new y coordinate of the window, relative to its parent. -} #if ENABLE_OVERLOADING eventConfigure_y , #endif getEventConfigureY , setEventConfigureY , ) 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.Objects.Window as Gdk.Window -- | Memory-managed wrapper type. newtype EventConfigure = EventConfigure (ManagedPtr EventConfigure) instance WrappedPtr EventConfigure where wrappedPtrCalloc = callocBytes 40 wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 40 >=> wrapPtr EventConfigure) wrappedPtrFree = Just ptr_to_g_free -- | Construct a `EventConfigure` struct initialized to zero. newZeroEventConfigure :: MonadIO m => m EventConfigure newZeroEventConfigure = liftIO $ wrappedPtrCalloc >>= wrapPtr EventConfigure instance tag ~ 'AttrSet => Constructible EventConfigure tag where new _ attrs = do o <- newZeroEventConfigure GI.Attributes.set o attrs return o -- | A convenience alias for `Nothing` :: `Maybe` `EventConfigure`. noEventConfigure :: Maybe EventConfigure noEventConfigure = Nothing {- | Get the value of the “@type@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventConfigure #type @ -} getEventConfigureType :: MonadIO m => EventConfigure -> m Gdk.Enums.EventType getEventConfigureType 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' eventConfigure [ #type 'Data.GI.Base.Attributes.:=' value ] @ -} setEventConfigureType :: MonadIO m => EventConfigure -> Gdk.Enums.EventType -> m () setEventConfigureType s val = liftIO $ withManagedPtr s $ \ptr -> do let val' = (fromIntegral . fromEnum) val poke (ptr `plusPtr` 0) (val' :: CInt) #if ENABLE_OVERLOADING data EventConfigureTypeFieldInfo instance AttrInfo EventConfigureTypeFieldInfo where type AttrAllowedOps EventConfigureTypeFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventConfigureTypeFieldInfo = (~) Gdk.Enums.EventType type AttrBaseTypeConstraint EventConfigureTypeFieldInfo = (~) EventConfigure type AttrGetType EventConfigureTypeFieldInfo = Gdk.Enums.EventType type AttrLabel EventConfigureTypeFieldInfo = "type" type AttrOrigin EventConfigureTypeFieldInfo = EventConfigure attrGet _ = getEventConfigureType attrSet _ = setEventConfigureType attrConstruct = undefined attrClear _ = undefined eventConfigure_type :: AttrLabelProxy "type" eventConfigure_type = AttrLabelProxy #endif {- | Get the value of the “@window@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventConfigure #window @ -} getEventConfigureWindow :: MonadIO m => EventConfigure -> m (Maybe Gdk.Window.Window) getEventConfigureWindow 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' eventConfigure [ #window 'Data.GI.Base.Attributes.:=' value ] @ -} setEventConfigureWindow :: MonadIO m => EventConfigure -> Ptr Gdk.Window.Window -> m () setEventConfigureWindow 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 @ -} clearEventConfigureWindow :: MonadIO m => EventConfigure -> m () clearEventConfigureWindow s = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window) #if ENABLE_OVERLOADING data EventConfigureWindowFieldInfo instance AttrInfo EventConfigureWindowFieldInfo where type AttrAllowedOps EventConfigureWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear] type AttrSetTypeConstraint EventConfigureWindowFieldInfo = (~) (Ptr Gdk.Window.Window) type AttrBaseTypeConstraint EventConfigureWindowFieldInfo = (~) EventConfigure type AttrGetType EventConfigureWindowFieldInfo = Maybe Gdk.Window.Window type AttrLabel EventConfigureWindowFieldInfo = "window" type AttrOrigin EventConfigureWindowFieldInfo = EventConfigure attrGet _ = getEventConfigureWindow attrSet _ = setEventConfigureWindow attrConstruct = undefined attrClear _ = clearEventConfigureWindow eventConfigure_window :: AttrLabelProxy "window" eventConfigure_window = AttrLabelProxy #endif {- | Get the value of the “@send_event@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventConfigure #sendEvent @ -} getEventConfigureSendEvent :: MonadIO m => EventConfigure -> m Int8 getEventConfigureSendEvent 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' eventConfigure [ #sendEvent 'Data.GI.Base.Attributes.:=' value ] @ -} setEventConfigureSendEvent :: MonadIO m => EventConfigure -> Int8 -> m () setEventConfigureSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 16) (val :: Int8) #if ENABLE_OVERLOADING data EventConfigureSendEventFieldInfo instance AttrInfo EventConfigureSendEventFieldInfo where type AttrAllowedOps EventConfigureSendEventFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventConfigureSendEventFieldInfo = (~) Int8 type AttrBaseTypeConstraint EventConfigureSendEventFieldInfo = (~) EventConfigure type AttrGetType EventConfigureSendEventFieldInfo = Int8 type AttrLabel EventConfigureSendEventFieldInfo = "send_event" type AttrOrigin EventConfigureSendEventFieldInfo = EventConfigure attrGet _ = getEventConfigureSendEvent attrSet _ = setEventConfigureSendEvent attrConstruct = undefined attrClear _ = undefined eventConfigure_sendEvent :: AttrLabelProxy "sendEvent" eventConfigure_sendEvent = AttrLabelProxy #endif {- | Get the value of the “@x@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventConfigure #x @ -} getEventConfigureX :: MonadIO m => EventConfigure -> m Int32 getEventConfigureX s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 20) :: IO Int32 return val {- | Set the value of the “@x@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventConfigure [ #x 'Data.GI.Base.Attributes.:=' value ] @ -} setEventConfigureX :: MonadIO m => EventConfigure -> Int32 -> m () setEventConfigureX s val = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 20) (val :: Int32) #if ENABLE_OVERLOADING data EventConfigureXFieldInfo instance AttrInfo EventConfigureXFieldInfo where type AttrAllowedOps EventConfigureXFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventConfigureXFieldInfo = (~) Int32 type AttrBaseTypeConstraint EventConfigureXFieldInfo = (~) EventConfigure type AttrGetType EventConfigureXFieldInfo = Int32 type AttrLabel EventConfigureXFieldInfo = "x" type AttrOrigin EventConfigureXFieldInfo = EventConfigure attrGet _ = getEventConfigureX attrSet _ = setEventConfigureX attrConstruct = undefined attrClear _ = undefined eventConfigure_x :: AttrLabelProxy "x" eventConfigure_x = AttrLabelProxy #endif {- | Get the value of the “@y@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventConfigure #y @ -} getEventConfigureY :: MonadIO m => EventConfigure -> m Int32 getEventConfigureY s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 24) :: IO Int32 return val {- | Set the value of the “@y@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventConfigure [ #y 'Data.GI.Base.Attributes.:=' value ] @ -} setEventConfigureY :: MonadIO m => EventConfigure -> Int32 -> m () setEventConfigureY s val = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 24) (val :: Int32) #if ENABLE_OVERLOADING data EventConfigureYFieldInfo instance AttrInfo EventConfigureYFieldInfo where type AttrAllowedOps EventConfigureYFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventConfigureYFieldInfo = (~) Int32 type AttrBaseTypeConstraint EventConfigureYFieldInfo = (~) EventConfigure type AttrGetType EventConfigureYFieldInfo = Int32 type AttrLabel EventConfigureYFieldInfo = "y" type AttrOrigin EventConfigureYFieldInfo = EventConfigure attrGet _ = getEventConfigureY attrSet _ = setEventConfigureY attrConstruct = undefined attrClear _ = undefined eventConfigure_y :: AttrLabelProxy "y" eventConfigure_y = AttrLabelProxy #endif {- | Get the value of the “@width@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventConfigure #width @ -} getEventConfigureWidth :: MonadIO m => EventConfigure -> m Int32 getEventConfigureWidth s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 28) :: IO Int32 return val {- | Set the value of the “@width@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventConfigure [ #width 'Data.GI.Base.Attributes.:=' value ] @ -} setEventConfigureWidth :: MonadIO m => EventConfigure -> Int32 -> m () setEventConfigureWidth s val = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 28) (val :: Int32) #if ENABLE_OVERLOADING data EventConfigureWidthFieldInfo instance AttrInfo EventConfigureWidthFieldInfo where type AttrAllowedOps EventConfigureWidthFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventConfigureWidthFieldInfo = (~) Int32 type AttrBaseTypeConstraint EventConfigureWidthFieldInfo = (~) EventConfigure type AttrGetType EventConfigureWidthFieldInfo = Int32 type AttrLabel EventConfigureWidthFieldInfo = "width" type AttrOrigin EventConfigureWidthFieldInfo = EventConfigure attrGet _ = getEventConfigureWidth attrSet _ = setEventConfigureWidth attrConstruct = undefined attrClear _ = undefined eventConfigure_width :: AttrLabelProxy "width" eventConfigure_width = AttrLabelProxy #endif {- | Get the value of the “@height@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.get' eventConfigure #height @ -} getEventConfigureHeight :: MonadIO m => EventConfigure -> m Int32 getEventConfigureHeight s = liftIO $ withManagedPtr s $ \ptr -> do val <- peek (ptr `plusPtr` 32) :: IO Int32 return val {- | Set the value of the “@height@” field. When is enabled, this is equivalent to @ 'Data.GI.Base.Attributes.set' eventConfigure [ #height 'Data.GI.Base.Attributes.:=' value ] @ -} setEventConfigureHeight :: MonadIO m => EventConfigure -> Int32 -> m () setEventConfigureHeight s val = liftIO $ withManagedPtr s $ \ptr -> do poke (ptr `plusPtr` 32) (val :: Int32) #if ENABLE_OVERLOADING data EventConfigureHeightFieldInfo instance AttrInfo EventConfigureHeightFieldInfo where type AttrAllowedOps EventConfigureHeightFieldInfo = '[ 'AttrSet, 'AttrGet] type AttrSetTypeConstraint EventConfigureHeightFieldInfo = (~) Int32 type AttrBaseTypeConstraint EventConfigureHeightFieldInfo = (~) EventConfigure type AttrGetType EventConfigureHeightFieldInfo = Int32 type AttrLabel EventConfigureHeightFieldInfo = "height" type AttrOrigin EventConfigureHeightFieldInfo = EventConfigure attrGet _ = getEventConfigureHeight attrSet _ = setEventConfigureHeight attrConstruct = undefined attrClear _ = undefined eventConfigure_height :: AttrLabelProxy "height" eventConfigure_height = AttrLabelProxy #endif #if ENABLE_OVERLOADING instance O.HasAttributeList EventConfigure type instance O.AttributeList EventConfigure = EventConfigureAttributeList type EventConfigureAttributeList = ('[ '("type", EventConfigureTypeFieldInfo), '("window", EventConfigureWindowFieldInfo), '("sendEvent", EventConfigureSendEventFieldInfo), '("x", EventConfigureXFieldInfo), '("y", EventConfigureYFieldInfo), '("width", EventConfigureWidthFieldInfo), '("height", EventConfigureHeightFieldInfo)] :: [(Symbol, *)]) #endif #if ENABLE_OVERLOADING type family ResolveEventConfigureMethod (t :: Symbol) (o :: *) :: * where ResolveEventConfigureMethod l o = O.MethodResolutionFailed l o instance (info ~ ResolveEventConfigureMethod t EventConfigure, O.MethodInfo info EventConfigure p) => OL.IsLabel t (EventConfigure -> 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