#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gdk.Structs.WindowAttr
(
WindowAttr(..) ,
newZeroWindowAttr ,
noWindowAttr ,
clearWindowAttrCursor ,
getWindowAttrCursor ,
setWindowAttrCursor ,
#if ENABLE_OVERLOADING
windowAttr_cursor ,
#endif
getWindowAttrEventMask ,
setWindowAttrEventMask ,
#if ENABLE_OVERLOADING
windowAttr_eventMask ,
#endif
getWindowAttrHeight ,
setWindowAttrHeight ,
#if ENABLE_OVERLOADING
windowAttr_height ,
#endif
getWindowAttrOverrideRedirect ,
setWindowAttrOverrideRedirect ,
#if ENABLE_OVERLOADING
windowAttr_overrideRedirect ,
#endif
clearWindowAttrTitle ,
getWindowAttrTitle ,
setWindowAttrTitle ,
#if ENABLE_OVERLOADING
windowAttr_title ,
#endif
getWindowAttrTypeHint ,
setWindowAttrTypeHint ,
#if ENABLE_OVERLOADING
windowAttr_typeHint ,
#endif
clearWindowAttrVisual ,
getWindowAttrVisual ,
setWindowAttrVisual ,
#if ENABLE_OVERLOADING
windowAttr_visual ,
#endif
getWindowAttrWclass ,
setWindowAttrWclass ,
#if ENABLE_OVERLOADING
windowAttr_wclass ,
#endif
getWindowAttrWidth ,
setWindowAttrWidth ,
#if ENABLE_OVERLOADING
windowAttr_width ,
#endif
getWindowAttrWindowType ,
setWindowAttrWindowType ,
#if ENABLE_OVERLOADING
windowAttr_windowType ,
#endif
clearWindowAttrWmclassClass ,
getWindowAttrWmclassClass ,
setWindowAttrWmclassClass ,
#if ENABLE_OVERLOADING
windowAttr_wmclassClass ,
#endif
clearWindowAttrWmclassName ,
getWindowAttrWmclassName ,
setWindowAttrWmclassName ,
#if ENABLE_OVERLOADING
windowAttr_wmclassName ,
#endif
getWindowAttrX ,
setWindowAttrX ,
#if ENABLE_OVERLOADING
windowAttr_x ,
#endif
getWindowAttrY ,
setWindowAttrY ,
#if ENABLE_OVERLOADING
windowAttr_y ,
#endif
) 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Visual as Gdk.Visual
newtype WindowAttr = WindowAttr (ManagedPtr WindowAttr)
instance WrappedPtr WindowAttr where
wrappedPtrCalloc = callocBytes 80
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 80 >=> wrapPtr WindowAttr)
wrappedPtrFree = Just ptr_to_g_free
newZeroWindowAttr :: MonadIO m => m WindowAttr
newZeroWindowAttr = liftIO $ wrappedPtrCalloc >>= wrapPtr WindowAttr
instance tag ~ 'AttrSet => Constructible WindowAttr tag where
new _ attrs = do
o <- newZeroWindowAttr
GI.Attributes.set o attrs
return o
noWindowAttr :: Maybe WindowAttr
noWindowAttr = Nothing
getWindowAttrTitle :: MonadIO m => WindowAttr -> m (Maybe T.Text)
getWindowAttrTitle s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CString
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- cstringToText val'
return val''
return result
setWindowAttrTitle :: MonadIO m => WindowAttr -> CString -> m ()
setWindowAttrTitle s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (val :: CString)
clearWindowAttrTitle :: MonadIO m => WindowAttr -> m ()
clearWindowAttrTitle s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)
#if ENABLE_OVERLOADING
data WindowAttrTitleFieldInfo
instance AttrInfo WindowAttrTitleFieldInfo where
type AttrAllowedOps WindowAttrTitleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrTitleFieldInfo = (~) CString
type AttrBaseTypeConstraint WindowAttrTitleFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrTitleFieldInfo = Maybe T.Text
type AttrLabel WindowAttrTitleFieldInfo = "title"
type AttrOrigin WindowAttrTitleFieldInfo = WindowAttr
attrGet _ = getWindowAttrTitle
attrSet _ = setWindowAttrTitle
attrConstruct = undefined
attrClear _ = clearWindowAttrTitle
windowAttr_title :: AttrLabelProxy "title"
windowAttr_title = AttrLabelProxy
#endif
getWindowAttrEventMask :: MonadIO m => WindowAttr -> m Int32
getWindowAttrEventMask s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO Int32
return val
setWindowAttrEventMask :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrEventMask s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Int32)
#if ENABLE_OVERLOADING
data WindowAttrEventMaskFieldInfo
instance AttrInfo WindowAttrEventMaskFieldInfo where
type AttrAllowedOps WindowAttrEventMaskFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrEventMaskFieldInfo = (~) Int32
type AttrBaseTypeConstraint WindowAttrEventMaskFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrEventMaskFieldInfo = Int32
type AttrLabel WindowAttrEventMaskFieldInfo = "event_mask"
type AttrOrigin WindowAttrEventMaskFieldInfo = WindowAttr
attrGet _ = getWindowAttrEventMask
attrSet _ = setWindowAttrEventMask
attrConstruct = undefined
attrClear _ = undefined
windowAttr_eventMask :: AttrLabelProxy "eventMask"
windowAttr_eventMask = AttrLabelProxy
#endif
getWindowAttrX :: MonadIO m => WindowAttr -> m Int32
getWindowAttrX s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 12) :: IO Int32
return val
setWindowAttrX :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrX s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 12) (val :: Int32)
#if ENABLE_OVERLOADING
data WindowAttrXFieldInfo
instance AttrInfo WindowAttrXFieldInfo where
type AttrAllowedOps WindowAttrXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrXFieldInfo = (~) Int32
type AttrBaseTypeConstraint WindowAttrXFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrXFieldInfo = Int32
type AttrLabel WindowAttrXFieldInfo = "x"
type AttrOrigin WindowAttrXFieldInfo = WindowAttr
attrGet _ = getWindowAttrX
attrSet _ = setWindowAttrX
attrConstruct = undefined
attrClear _ = undefined
windowAttr_x :: AttrLabelProxy "x"
windowAttr_x = AttrLabelProxy
#endif
getWindowAttrY :: MonadIO m => WindowAttr -> m Int32
getWindowAttrY s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int32
return val
setWindowAttrY :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrY s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int32)
#if ENABLE_OVERLOADING
data WindowAttrYFieldInfo
instance AttrInfo WindowAttrYFieldInfo where
type AttrAllowedOps WindowAttrYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrYFieldInfo = (~) Int32
type AttrBaseTypeConstraint WindowAttrYFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrYFieldInfo = Int32
type AttrLabel WindowAttrYFieldInfo = "y"
type AttrOrigin WindowAttrYFieldInfo = WindowAttr
attrGet _ = getWindowAttrY
attrSet _ = setWindowAttrY
attrConstruct = undefined
attrClear _ = undefined
windowAttr_y :: AttrLabelProxy "y"
windowAttr_y = AttrLabelProxy
#endif
getWindowAttrWidth :: MonadIO m => WindowAttr -> m Int32
getWindowAttrWidth s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 20) :: IO Int32
return val
setWindowAttrWidth :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrWidth s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 20) (val :: Int32)
#if ENABLE_OVERLOADING
data WindowAttrWidthFieldInfo
instance AttrInfo WindowAttrWidthFieldInfo where
type AttrAllowedOps WindowAttrWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrWidthFieldInfo = (~) Int32
type AttrBaseTypeConstraint WindowAttrWidthFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrWidthFieldInfo = Int32
type AttrLabel WindowAttrWidthFieldInfo = "width"
type AttrOrigin WindowAttrWidthFieldInfo = WindowAttr
attrGet _ = getWindowAttrWidth
attrSet _ = setWindowAttrWidth
attrConstruct = undefined
attrClear _ = undefined
windowAttr_width :: AttrLabelProxy "width"
windowAttr_width = AttrLabelProxy
#endif
getWindowAttrHeight :: MonadIO m => WindowAttr -> m Int32
getWindowAttrHeight s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO Int32
return val
setWindowAttrHeight :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrHeight s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (val :: Int32)
#if ENABLE_OVERLOADING
data WindowAttrHeightFieldInfo
instance AttrInfo WindowAttrHeightFieldInfo where
type AttrAllowedOps WindowAttrHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrHeightFieldInfo = (~) Int32
type AttrBaseTypeConstraint WindowAttrHeightFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrHeightFieldInfo = Int32
type AttrLabel WindowAttrHeightFieldInfo = "height"
type AttrOrigin WindowAttrHeightFieldInfo = WindowAttr
attrGet _ = getWindowAttrHeight
attrSet _ = setWindowAttrHeight
attrConstruct = undefined
attrClear _ = undefined
windowAttr_height :: AttrLabelProxy "height"
windowAttr_height = AttrLabelProxy
#endif
getWindowAttrWclass :: MonadIO m => WindowAttr -> m Gdk.Enums.WindowWindowClass
getWindowAttrWclass s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 28) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setWindowAttrWclass :: MonadIO m => WindowAttr -> Gdk.Enums.WindowWindowClass -> m ()
setWindowAttrWclass s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 28) (val' :: CUInt)
#if ENABLE_OVERLOADING
data WindowAttrWclassFieldInfo
instance AttrInfo WindowAttrWclassFieldInfo where
type AttrAllowedOps WindowAttrWclassFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrWclassFieldInfo = (~) Gdk.Enums.WindowWindowClass
type AttrBaseTypeConstraint WindowAttrWclassFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrWclassFieldInfo = Gdk.Enums.WindowWindowClass
type AttrLabel WindowAttrWclassFieldInfo = "wclass"
type AttrOrigin WindowAttrWclassFieldInfo = WindowAttr
attrGet _ = getWindowAttrWclass
attrSet _ = setWindowAttrWclass
attrConstruct = undefined
attrClear _ = undefined
windowAttr_wclass :: AttrLabelProxy "wclass"
windowAttr_wclass = AttrLabelProxy
#endif
getWindowAttrVisual :: MonadIO m => WindowAttr -> m (Maybe Gdk.Visual.Visual)
getWindowAttrVisual s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO (Ptr Gdk.Visual.Visual)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.Visual.Visual) val'
return val''
return result
setWindowAttrVisual :: MonadIO m => WindowAttr -> Ptr Gdk.Visual.Visual -> m ()
setWindowAttrVisual s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (val :: Ptr Gdk.Visual.Visual)
clearWindowAttrVisual :: MonadIO m => WindowAttr -> m ()
clearWindowAttrVisual s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (FP.nullPtr :: Ptr Gdk.Visual.Visual)
#if ENABLE_OVERLOADING
data WindowAttrVisualFieldInfo
instance AttrInfo WindowAttrVisualFieldInfo where
type AttrAllowedOps WindowAttrVisualFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrVisualFieldInfo = (~) (Ptr Gdk.Visual.Visual)
type AttrBaseTypeConstraint WindowAttrVisualFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrVisualFieldInfo = Maybe Gdk.Visual.Visual
type AttrLabel WindowAttrVisualFieldInfo = "visual"
type AttrOrigin WindowAttrVisualFieldInfo = WindowAttr
attrGet _ = getWindowAttrVisual
attrSet _ = setWindowAttrVisual
attrConstruct = undefined
attrClear _ = clearWindowAttrVisual
windowAttr_visual :: AttrLabelProxy "visual"
windowAttr_visual = AttrLabelProxy
#endif
getWindowAttrWindowType :: MonadIO m => WindowAttr -> m Gdk.Enums.WindowType
getWindowAttrWindowType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setWindowAttrWindowType :: MonadIO m => WindowAttr -> Gdk.Enums.WindowType -> m ()
setWindowAttrWindowType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 40) (val' :: CUInt)
#if ENABLE_OVERLOADING
data WindowAttrWindowTypeFieldInfo
instance AttrInfo WindowAttrWindowTypeFieldInfo where
type AttrAllowedOps WindowAttrWindowTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrWindowTypeFieldInfo = (~) Gdk.Enums.WindowType
type AttrBaseTypeConstraint WindowAttrWindowTypeFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrWindowTypeFieldInfo = Gdk.Enums.WindowType
type AttrLabel WindowAttrWindowTypeFieldInfo = "window_type"
type AttrOrigin WindowAttrWindowTypeFieldInfo = WindowAttr
attrGet _ = getWindowAttrWindowType
attrSet _ = setWindowAttrWindowType
attrConstruct = undefined
attrClear _ = undefined
windowAttr_windowType :: AttrLabelProxy "windowType"
windowAttr_windowType = AttrLabelProxy
#endif
getWindowAttrCursor :: MonadIO m => WindowAttr -> m (Maybe Gdk.Cursor.Cursor)
getWindowAttrCursor s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO (Ptr Gdk.Cursor.Cursor)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.Cursor.Cursor) val'
return val''
return result
setWindowAttrCursor :: MonadIO m => WindowAttr -> Ptr Gdk.Cursor.Cursor -> m ()
setWindowAttrCursor s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 48) (val :: Ptr Gdk.Cursor.Cursor)
clearWindowAttrCursor :: MonadIO m => WindowAttr -> m ()
clearWindowAttrCursor s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 48) (FP.nullPtr :: Ptr Gdk.Cursor.Cursor)
#if ENABLE_OVERLOADING
data WindowAttrCursorFieldInfo
instance AttrInfo WindowAttrCursorFieldInfo where
type AttrAllowedOps WindowAttrCursorFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrCursorFieldInfo = (~) (Ptr Gdk.Cursor.Cursor)
type AttrBaseTypeConstraint WindowAttrCursorFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrCursorFieldInfo = Maybe Gdk.Cursor.Cursor
type AttrLabel WindowAttrCursorFieldInfo = "cursor"
type AttrOrigin WindowAttrCursorFieldInfo = WindowAttr
attrGet _ = getWindowAttrCursor
attrSet _ = setWindowAttrCursor
attrConstruct = undefined
attrClear _ = clearWindowAttrCursor
windowAttr_cursor :: AttrLabelProxy "cursor"
windowAttr_cursor = AttrLabelProxy
#endif
getWindowAttrWmclassName :: MonadIO m => WindowAttr -> m (Maybe T.Text)
getWindowAttrWmclassName s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 56) :: IO CString
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- cstringToText val'
return val''
return result
setWindowAttrWmclassName :: MonadIO m => WindowAttr -> CString -> m ()
setWindowAttrWmclassName s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (val :: CString)
clearWindowAttrWmclassName :: MonadIO m => WindowAttr -> m ()
clearWindowAttrWmclassName s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (FP.nullPtr :: CString)
#if ENABLE_OVERLOADING
data WindowAttrWmclassNameFieldInfo
instance AttrInfo WindowAttrWmclassNameFieldInfo where
type AttrAllowedOps WindowAttrWmclassNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrWmclassNameFieldInfo = (~) CString
type AttrBaseTypeConstraint WindowAttrWmclassNameFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrWmclassNameFieldInfo = Maybe T.Text
type AttrLabel WindowAttrWmclassNameFieldInfo = "wmclass_name"
type AttrOrigin WindowAttrWmclassNameFieldInfo = WindowAttr
attrGet _ = getWindowAttrWmclassName
attrSet _ = setWindowAttrWmclassName
attrConstruct = undefined
attrClear _ = clearWindowAttrWmclassName
windowAttr_wmclassName :: AttrLabelProxy "wmclassName"
windowAttr_wmclassName = AttrLabelProxy
#endif
getWindowAttrWmclassClass :: MonadIO m => WindowAttr -> m (Maybe T.Text)
getWindowAttrWmclassClass s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 64) :: IO CString
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- cstringToText val'
return val''
return result
setWindowAttrWmclassClass :: MonadIO m => WindowAttr -> CString -> m ()
setWindowAttrWmclassClass s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 64) (val :: CString)
clearWindowAttrWmclassClass :: MonadIO m => WindowAttr -> m ()
clearWindowAttrWmclassClass s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 64) (FP.nullPtr :: CString)
#if ENABLE_OVERLOADING
data WindowAttrWmclassClassFieldInfo
instance AttrInfo WindowAttrWmclassClassFieldInfo where
type AttrAllowedOps WindowAttrWmclassClassFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrWmclassClassFieldInfo = (~) CString
type AttrBaseTypeConstraint WindowAttrWmclassClassFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrWmclassClassFieldInfo = Maybe T.Text
type AttrLabel WindowAttrWmclassClassFieldInfo = "wmclass_class"
type AttrOrigin WindowAttrWmclassClassFieldInfo = WindowAttr
attrGet _ = getWindowAttrWmclassClass
attrSet _ = setWindowAttrWmclassClass
attrConstruct = undefined
attrClear _ = clearWindowAttrWmclassClass
windowAttr_wmclassClass :: AttrLabelProxy "wmclassClass"
windowAttr_wmclassClass = AttrLabelProxy
#endif
getWindowAttrOverrideRedirect :: MonadIO m => WindowAttr -> m Bool
getWindowAttrOverrideRedirect s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 72) :: IO CInt
let val' = (/= 0) val
return val'
setWindowAttrOverrideRedirect :: MonadIO m => WindowAttr -> Bool -> m ()
setWindowAttrOverrideRedirect s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 72) (val' :: CInt)
#if ENABLE_OVERLOADING
data WindowAttrOverrideRedirectFieldInfo
instance AttrInfo WindowAttrOverrideRedirectFieldInfo where
type AttrAllowedOps WindowAttrOverrideRedirectFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrOverrideRedirectFieldInfo = (~) Bool
type AttrBaseTypeConstraint WindowAttrOverrideRedirectFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrOverrideRedirectFieldInfo = Bool
type AttrLabel WindowAttrOverrideRedirectFieldInfo = "override_redirect"
type AttrOrigin WindowAttrOverrideRedirectFieldInfo = WindowAttr
attrGet _ = getWindowAttrOverrideRedirect
attrSet _ = setWindowAttrOverrideRedirect
attrConstruct = undefined
attrClear _ = undefined
windowAttr_overrideRedirect :: AttrLabelProxy "overrideRedirect"
windowAttr_overrideRedirect = AttrLabelProxy
#endif
getWindowAttrTypeHint :: MonadIO m => WindowAttr -> m Gdk.Enums.WindowTypeHint
getWindowAttrTypeHint s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 76) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setWindowAttrTypeHint :: MonadIO m => WindowAttr -> Gdk.Enums.WindowTypeHint -> m ()
setWindowAttrTypeHint s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 76) (val' :: CUInt)
#if ENABLE_OVERLOADING
data WindowAttrTypeHintFieldInfo
instance AttrInfo WindowAttrTypeHintFieldInfo where
type AttrAllowedOps WindowAttrTypeHintFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrTypeHintFieldInfo = (~) Gdk.Enums.WindowTypeHint
type AttrBaseTypeConstraint WindowAttrTypeHintFieldInfo = (~) WindowAttr
type AttrGetType WindowAttrTypeHintFieldInfo = Gdk.Enums.WindowTypeHint
type AttrLabel WindowAttrTypeHintFieldInfo = "type_hint"
type AttrOrigin WindowAttrTypeHintFieldInfo = WindowAttr
attrGet _ = getWindowAttrTypeHint
attrSet _ = setWindowAttrTypeHint
attrConstruct = undefined
attrClear _ = undefined
windowAttr_typeHint :: AttrLabelProxy "typeHint"
windowAttr_typeHint = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList WindowAttr
type instance O.AttributeList WindowAttr = WindowAttrAttributeList
type WindowAttrAttributeList = ('[ '("title", WindowAttrTitleFieldInfo), '("eventMask", WindowAttrEventMaskFieldInfo), '("x", WindowAttrXFieldInfo), '("y", WindowAttrYFieldInfo), '("width", WindowAttrWidthFieldInfo), '("height", WindowAttrHeightFieldInfo), '("wclass", WindowAttrWclassFieldInfo), '("visual", WindowAttrVisualFieldInfo), '("windowType", WindowAttrWindowTypeFieldInfo), '("cursor", WindowAttrCursorFieldInfo), '("wmclassName", WindowAttrWmclassNameFieldInfo), '("wmclassClass", WindowAttrWmclassClassFieldInfo), '("overrideRedirect", WindowAttrOverrideRedirectFieldInfo), '("typeHint", WindowAttrTypeHintFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveWindowAttrMethod (t :: Symbol) (o :: *) :: * where
ResolveWindowAttrMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveWindowAttrMethod t WindowAttr, O.MethodInfo info WindowAttr p) => O.IsLabelProxy t (WindowAttr -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveWindowAttrMethod t WindowAttr, O.MethodInfo info WindowAttr p) => O.IsLabel t (WindowAttr -> 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
#endif