{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.WindowAttr
(
WindowAttr(..) ,
newZeroWindowAttr ,
#if defined(ENABLE_OVERLOADING)
ResolveWindowAttrMethod ,
#endif
clearWindowAttrCursor ,
getWindowAttrCursor ,
setWindowAttrCursor ,
#if defined(ENABLE_OVERLOADING)
windowAttr_cursor ,
#endif
getWindowAttrEventMask ,
setWindowAttrEventMask ,
#if defined(ENABLE_OVERLOADING)
windowAttr_eventMask ,
#endif
getWindowAttrHeight ,
setWindowAttrHeight ,
#if defined(ENABLE_OVERLOADING)
windowAttr_height ,
#endif
getWindowAttrOverrideRedirect ,
setWindowAttrOverrideRedirect ,
#if defined(ENABLE_OVERLOADING)
windowAttr_overrideRedirect ,
#endif
clearWindowAttrTitle ,
getWindowAttrTitle ,
setWindowAttrTitle ,
#if defined(ENABLE_OVERLOADING)
windowAttr_title ,
#endif
getWindowAttrTypeHint ,
setWindowAttrTypeHint ,
#if defined(ENABLE_OVERLOADING)
windowAttr_typeHint ,
#endif
clearWindowAttrVisual ,
getWindowAttrVisual ,
setWindowAttrVisual ,
#if defined(ENABLE_OVERLOADING)
windowAttr_visual ,
#endif
getWindowAttrWclass ,
setWindowAttrWclass ,
#if defined(ENABLE_OVERLOADING)
windowAttr_wclass ,
#endif
getWindowAttrWidth ,
setWindowAttrWidth ,
#if defined(ENABLE_OVERLOADING)
windowAttr_width ,
#endif
getWindowAttrWindowType ,
setWindowAttrWindowType ,
#if defined(ENABLE_OVERLOADING)
windowAttr_windowType ,
#endif
clearWindowAttrWmclassClass ,
getWindowAttrWmclassClass ,
setWindowAttrWmclassClass ,
#if defined(ENABLE_OVERLOADING)
windowAttr_wmclassClass ,
#endif
clearWindowAttrWmclassName ,
getWindowAttrWmclassName ,
setWindowAttrWmclassName ,
#if defined(ENABLE_OVERLOADING)
windowAttr_wmclassName ,
#endif
getWindowAttrX ,
setWindowAttrX ,
#if defined(ENABLE_OVERLOADING)
windowAttr_x ,
#endif
getWindowAttrY ,
setWindowAttrY ,
#if defined(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.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.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 (SP.ManagedPtr WindowAttr)
deriving (WindowAttr -> WindowAttr -> Bool
(WindowAttr -> WindowAttr -> Bool)
-> (WindowAttr -> WindowAttr -> Bool) -> Eq WindowAttr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowAttr -> WindowAttr -> Bool
$c/= :: WindowAttr -> WindowAttr -> Bool
== :: WindowAttr -> WindowAttr -> Bool
$c== :: WindowAttr -> WindowAttr -> Bool
Eq)
instance SP.ManagedPtrNewtype WindowAttr where
toManagedPtr :: WindowAttr -> ManagedPtr WindowAttr
toManagedPtr (WindowAttr ManagedPtr WindowAttr
p) = ManagedPtr WindowAttr
p
instance BoxedPtr WindowAttr where
boxedPtrCopy :: WindowAttr -> IO WindowAttr
boxedPtrCopy = \WindowAttr
p -> WindowAttr -> (Ptr WindowAttr -> IO WindowAttr) -> IO WindowAttr
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr WindowAttr
p (Int -> Ptr WindowAttr -> IO (Ptr WindowAttr)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
80 (Ptr WindowAttr -> IO (Ptr WindowAttr))
-> (Ptr WindowAttr -> IO WindowAttr)
-> Ptr WindowAttr
-> IO WindowAttr
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr WindowAttr -> WindowAttr)
-> Ptr WindowAttr -> IO WindowAttr
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr WindowAttr -> WindowAttr
WindowAttr)
boxedPtrFree :: WindowAttr -> IO ()
boxedPtrFree = \WindowAttr
x -> WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr WindowAttr
x Ptr WindowAttr -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr WindowAttr where
boxedPtrCalloc :: IO (Ptr WindowAttr)
boxedPtrCalloc = Int -> IO (Ptr WindowAttr)
forall a. Int -> IO (Ptr a)
callocBytes Int
80
newZeroWindowAttr :: MonadIO m => m WindowAttr
newZeroWindowAttr :: m WindowAttr
newZeroWindowAttr = IO WindowAttr -> m WindowAttr
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WindowAttr -> m WindowAttr) -> IO WindowAttr -> m WindowAttr
forall a b. (a -> b) -> a -> b
$ IO (Ptr WindowAttr)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr WindowAttr)
-> (Ptr WindowAttr -> IO WindowAttr) -> IO WindowAttr
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr WindowAttr -> WindowAttr)
-> Ptr WindowAttr -> IO WindowAttr
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr WindowAttr -> WindowAttr
WindowAttr
instance tag ~ 'AttrSet => Constructible WindowAttr tag where
new :: (ManagedPtr WindowAttr -> WindowAttr)
-> [AttrOp WindowAttr tag] -> m WindowAttr
new ManagedPtr WindowAttr -> WindowAttr
_ [AttrOp WindowAttr tag]
attrs = do
WindowAttr
o <- m WindowAttr
forall (m :: * -> *). MonadIO m => m WindowAttr
newZeroWindowAttr
WindowAttr -> [AttrOp WindowAttr 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set WindowAttr
o [AttrOp WindowAttr tag]
[AttrOp WindowAttr 'AttrSet]
attrs
WindowAttr -> m WindowAttr
forall (m :: * -> *) a. Monad m => a -> m a
return WindowAttr
o
getWindowAttrTitle :: MonadIO m => WindowAttr -> m (Maybe T.Text)
getWindowAttrTitle :: WindowAttr -> m (Maybe Text)
getWindowAttrTitle WindowAttr
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ WindowAttr
-> (Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CString
Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setWindowAttrTitle :: MonadIO m => WindowAttr -> CString -> m ()
setWindowAttrTitle :: WindowAttr -> CString -> m ()
setWindowAttrTitle WindowAttr
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
val :: CString)
clearWindowAttrTitle :: MonadIO m => WindowAttr -> m ()
clearWindowAttrTitle :: WindowAttr -> m ()
clearWindowAttrTitle WindowAttr
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data WindowAttrTitleFieldInfo
instance AttrInfo WindowAttrTitleFieldInfo where
type AttrBaseTypeConstraint WindowAttrTitleFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrTitleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrTitleFieldInfo = (~) CString
type AttrTransferTypeConstraint WindowAttrTitleFieldInfo = (~)CString
type AttrTransferType WindowAttrTitleFieldInfo = CString
type AttrGetType WindowAttrTitleFieldInfo = Maybe T.Text
type AttrLabel WindowAttrTitleFieldInfo = "title"
type AttrOrigin WindowAttrTitleFieldInfo = WindowAttr
attrGet = getWindowAttrTitle
attrSet = setWindowAttrTitle
attrConstruct = undefined
attrClear = clearWindowAttrTitle
attrTransfer _ v = do
return v
windowAttr_title :: AttrLabelProxy "title"
windowAttr_title = AttrLabelProxy
#endif
getWindowAttrEventMask :: MonadIO m => WindowAttr -> m Int32
getWindowAttrEventMask :: WindowAttr -> m Int32
getWindowAttrEventMask WindowAttr
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO Int32) -> IO Int32)
-> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWindowAttrEventMask :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrEventMask :: WindowAttr -> Int32 -> m ()
setWindowAttrEventMask WindowAttr
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WindowAttrEventMaskFieldInfo
instance AttrInfo WindowAttrEventMaskFieldInfo where
type AttrBaseTypeConstraint WindowAttrEventMaskFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrEventMaskFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrEventMaskFieldInfo = (~) Int32
type AttrTransferTypeConstraint WindowAttrEventMaskFieldInfo = (~)Int32
type AttrTransferType WindowAttrEventMaskFieldInfo = Int32
type AttrGetType WindowAttrEventMaskFieldInfo = Int32
type AttrLabel WindowAttrEventMaskFieldInfo = "event_mask"
type AttrOrigin WindowAttrEventMaskFieldInfo = WindowAttr
attrGet = getWindowAttrEventMask
attrSet = setWindowAttrEventMask
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_eventMask :: AttrLabelProxy "eventMask"
windowAttr_eventMask = AttrLabelProxy
#endif
getWindowAttrX :: MonadIO m => WindowAttr -> m Int32
getWindowAttrX :: WindowAttr -> m Int32
getWindowAttrX WindowAttr
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO Int32) -> IO Int32)
-> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWindowAttrX :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrX :: WindowAttr -> Int32 -> m ()
setWindowAttrX WindowAttr
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WindowAttrXFieldInfo
instance AttrInfo WindowAttrXFieldInfo where
type AttrBaseTypeConstraint WindowAttrXFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrXFieldInfo = (~) Int32
type AttrTransferTypeConstraint WindowAttrXFieldInfo = (~)Int32
type AttrTransferType WindowAttrXFieldInfo = Int32
type AttrGetType WindowAttrXFieldInfo = Int32
type AttrLabel WindowAttrXFieldInfo = "x"
type AttrOrigin WindowAttrXFieldInfo = WindowAttr
attrGet = getWindowAttrX
attrSet = setWindowAttrX
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_x :: AttrLabelProxy "x"
windowAttr_x = AttrLabelProxy
#endif
getWindowAttrY :: MonadIO m => WindowAttr -> m Int32
getWindowAttrY :: WindowAttr -> m Int32
getWindowAttrY WindowAttr
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO Int32) -> IO Int32)
-> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWindowAttrY :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrY :: WindowAttr -> Int32 -> m ()
setWindowAttrY WindowAttr
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WindowAttrYFieldInfo
instance AttrInfo WindowAttrYFieldInfo where
type AttrBaseTypeConstraint WindowAttrYFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrYFieldInfo = (~) Int32
type AttrTransferTypeConstraint WindowAttrYFieldInfo = (~)Int32
type AttrTransferType WindowAttrYFieldInfo = Int32
type AttrGetType WindowAttrYFieldInfo = Int32
type AttrLabel WindowAttrYFieldInfo = "y"
type AttrOrigin WindowAttrYFieldInfo = WindowAttr
attrGet = getWindowAttrY
attrSet = setWindowAttrY
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_y :: AttrLabelProxy "y"
windowAttr_y = AttrLabelProxy
#endif
getWindowAttrWidth :: MonadIO m => WindowAttr -> m Int32
getWindowAttrWidth :: WindowAttr -> m Int32
getWindowAttrWidth WindowAttr
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO Int32) -> IO Int32)
-> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWindowAttrWidth :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrWidth :: WindowAttr -> Int32 -> m ()
setWindowAttrWidth WindowAttr
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WindowAttrWidthFieldInfo
instance AttrInfo WindowAttrWidthFieldInfo where
type AttrBaseTypeConstraint WindowAttrWidthFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrWidthFieldInfo = (~) Int32
type AttrTransferTypeConstraint WindowAttrWidthFieldInfo = (~)Int32
type AttrTransferType WindowAttrWidthFieldInfo = Int32
type AttrGetType WindowAttrWidthFieldInfo = Int32
type AttrLabel WindowAttrWidthFieldInfo = "width"
type AttrOrigin WindowAttrWidthFieldInfo = WindowAttr
attrGet = getWindowAttrWidth
attrSet = setWindowAttrWidth
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_width :: AttrLabelProxy "width"
windowAttr_width = AttrLabelProxy
#endif
getWindowAttrHeight :: MonadIO m => WindowAttr -> m Int32
getWindowAttrHeight :: WindowAttr -> m Int32
getWindowAttrHeight WindowAttr
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO Int32) -> IO Int32)
-> (Ptr WindowAttr -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setWindowAttrHeight :: MonadIO m => WindowAttr -> Int32 -> m ()
setWindowAttrHeight :: WindowAttr -> Int32 -> m ()
setWindowAttrHeight WindowAttr
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data WindowAttrHeightFieldInfo
instance AttrInfo WindowAttrHeightFieldInfo where
type AttrBaseTypeConstraint WindowAttrHeightFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrHeightFieldInfo = (~) Int32
type AttrTransferTypeConstraint WindowAttrHeightFieldInfo = (~)Int32
type AttrTransferType WindowAttrHeightFieldInfo = Int32
type AttrGetType WindowAttrHeightFieldInfo = Int32
type AttrLabel WindowAttrHeightFieldInfo = "height"
type AttrOrigin WindowAttrHeightFieldInfo = WindowAttr
attrGet = getWindowAttrHeight
attrSet = setWindowAttrHeight
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_height :: AttrLabelProxy "height"
windowAttr_height = AttrLabelProxy
#endif
getWindowAttrWclass :: MonadIO m => WindowAttr -> m Gdk.Enums.WindowWindowClass
getWindowAttrWclass :: WindowAttr -> m WindowWindowClass
getWindowAttrWclass WindowAttr
s = IO WindowWindowClass -> m WindowWindowClass
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WindowWindowClass -> m WindowWindowClass)
-> IO WindowWindowClass -> m WindowWindowClass
forall a b. (a -> b) -> a -> b
$ WindowAttr
-> (Ptr WindowAttr -> IO WindowWindowClass) -> IO WindowWindowClass
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO WindowWindowClass) -> IO WindowWindowClass)
-> (Ptr WindowAttr -> IO WindowWindowClass) -> IO WindowWindowClass
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28) :: IO CUInt
let val' :: WindowWindowClass
val' = (Int -> WindowWindowClass
forall a. Enum a => Int -> a
toEnum (Int -> WindowWindowClass)
-> (CUInt -> Int) -> CUInt -> WindowWindowClass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
WindowWindowClass -> IO WindowWindowClass
forall (m :: * -> *) a. Monad m => a -> m a
return WindowWindowClass
val'
setWindowAttrWclass :: MonadIO m => WindowAttr -> Gdk.Enums.WindowWindowClass -> m ()
setWindowAttrWclass :: WindowAttr -> WindowWindowClass -> m ()
setWindowAttrWclass WindowAttr
s WindowWindowClass
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (WindowWindowClass -> Int) -> WindowWindowClass -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowWindowClass -> Int
forall a. Enum a => a -> Int
fromEnum) WindowWindowClass
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data WindowAttrWclassFieldInfo
instance AttrInfo WindowAttrWclassFieldInfo where
type AttrBaseTypeConstraint WindowAttrWclassFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrWclassFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrWclassFieldInfo = (~) Gdk.Enums.WindowWindowClass
type AttrTransferTypeConstraint WindowAttrWclassFieldInfo = (~)Gdk.Enums.WindowWindowClass
type AttrTransferType WindowAttrWclassFieldInfo = Gdk.Enums.WindowWindowClass
type AttrGetType WindowAttrWclassFieldInfo = Gdk.Enums.WindowWindowClass
type AttrLabel WindowAttrWclassFieldInfo = "wclass"
type AttrOrigin WindowAttrWclassFieldInfo = WindowAttr
attrGet = getWindowAttrWclass
attrSet = setWindowAttrWclass
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_wclass :: AttrLabelProxy "wclass"
windowAttr_wclass = AttrLabelProxy
#endif
getWindowAttrVisual :: MonadIO m => WindowAttr -> m (Maybe Gdk.Visual.Visual)
getWindowAttrVisual :: WindowAttr -> m (Maybe Visual)
getWindowAttrVisual WindowAttr
s = IO (Maybe Visual) -> m (Maybe Visual)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Visual) -> m (Maybe Visual))
-> IO (Maybe Visual) -> m (Maybe Visual)
forall a b. (a -> b) -> a -> b
$ WindowAttr
-> (Ptr WindowAttr -> IO (Maybe Visual)) -> IO (Maybe Visual)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO (Maybe Visual)) -> IO (Maybe Visual))
-> (Ptr WindowAttr -> IO (Maybe Visual)) -> IO (Maybe Visual)
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr Visual
val <- Ptr (Ptr Visual) -> IO (Ptr Visual)
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr (Ptr Visual)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO (Ptr Gdk.Visual.Visual)
Maybe Visual
result <- Ptr Visual -> (Ptr Visual -> IO Visual) -> IO (Maybe Visual)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Visual
val ((Ptr Visual -> IO Visual) -> IO (Maybe Visual))
-> (Ptr Visual -> IO Visual) -> IO (Maybe Visual)
forall a b. (a -> b) -> a -> b
$ \Ptr Visual
val' -> do
Visual
val'' <- ((ManagedPtr Visual -> Visual) -> Ptr Visual -> IO Visual
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Visual -> Visual
Gdk.Visual.Visual) Ptr Visual
val'
Visual -> IO Visual
forall (m :: * -> *) a. Monad m => a -> m a
return Visual
val''
Maybe Visual -> IO (Maybe Visual)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Visual
result
setWindowAttrVisual :: MonadIO m => WindowAttr -> Ptr Gdk.Visual.Visual -> m ()
setWindowAttrVisual :: WindowAttr -> Ptr Visual -> m ()
setWindowAttrVisual WindowAttr
s Ptr Visual
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr (Ptr Visual) -> Ptr Visual -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr (Ptr Visual)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Ptr Visual
val :: Ptr Gdk.Visual.Visual)
clearWindowAttrVisual :: MonadIO m => WindowAttr -> m ()
clearWindowAttrVisual :: WindowAttr -> m ()
clearWindowAttrVisual WindowAttr
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr (Ptr Visual) -> Ptr Visual -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr (Ptr Visual)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (Ptr Visual
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Visual.Visual)
#if defined(ENABLE_OVERLOADING)
data WindowAttrVisualFieldInfo
instance AttrInfo WindowAttrVisualFieldInfo where
type AttrBaseTypeConstraint WindowAttrVisualFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrVisualFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrVisualFieldInfo = (~) (Ptr Gdk.Visual.Visual)
type AttrTransferTypeConstraint WindowAttrVisualFieldInfo = (~)(Ptr Gdk.Visual.Visual)
type AttrTransferType WindowAttrVisualFieldInfo = (Ptr Gdk.Visual.Visual)
type AttrGetType WindowAttrVisualFieldInfo = Maybe Gdk.Visual.Visual
type AttrLabel WindowAttrVisualFieldInfo = "visual"
type AttrOrigin WindowAttrVisualFieldInfo = WindowAttr
attrGet = getWindowAttrVisual
attrSet = setWindowAttrVisual
attrConstruct = undefined
attrClear = clearWindowAttrVisual
attrTransfer _ v = do
return v
windowAttr_visual :: AttrLabelProxy "visual"
windowAttr_visual = AttrLabelProxy
#endif
getWindowAttrWindowType :: MonadIO m => WindowAttr -> m Gdk.Enums.WindowType
getWindowAttrWindowType :: WindowAttr -> m WindowType
getWindowAttrWindowType WindowAttr
s = IO WindowType -> m WindowType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WindowType -> m WindowType) -> IO WindowType -> m WindowType
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO WindowType) -> IO WindowType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO WindowType) -> IO WindowType)
-> (Ptr WindowAttr -> IO WindowType) -> IO WindowType
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO CUInt
let val' :: WindowType
val' = (Int -> WindowType
forall a. Enum a => Int -> a
toEnum (Int -> WindowType) -> (CUInt -> Int) -> CUInt -> WindowType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
WindowType -> IO WindowType
forall (m :: * -> *) a. Monad m => a -> m a
return WindowType
val'
setWindowAttrWindowType :: MonadIO m => WindowAttr -> Gdk.Enums.WindowType -> m ()
setWindowAttrWindowType :: WindowAttr -> WindowType -> m ()
setWindowAttrWindowType WindowAttr
s WindowType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (WindowType -> Int) -> WindowType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowType -> Int
forall a. Enum a => a -> Int
fromEnum) WindowType
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data WindowAttrWindowTypeFieldInfo
instance AttrInfo WindowAttrWindowTypeFieldInfo where
type AttrBaseTypeConstraint WindowAttrWindowTypeFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrWindowTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrWindowTypeFieldInfo = (~) Gdk.Enums.WindowType
type AttrTransferTypeConstraint WindowAttrWindowTypeFieldInfo = (~)Gdk.Enums.WindowType
type AttrTransferType WindowAttrWindowTypeFieldInfo = Gdk.Enums.WindowType
type AttrGetType WindowAttrWindowTypeFieldInfo = Gdk.Enums.WindowType
type AttrLabel WindowAttrWindowTypeFieldInfo = "window_type"
type AttrOrigin WindowAttrWindowTypeFieldInfo = WindowAttr
attrGet = getWindowAttrWindowType
attrSet = setWindowAttrWindowType
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_windowType :: AttrLabelProxy "windowType"
windowAttr_windowType = AttrLabelProxy
#endif
getWindowAttrCursor :: MonadIO m => WindowAttr -> m (Maybe Gdk.Cursor.Cursor)
getWindowAttrCursor :: WindowAttr -> m (Maybe Cursor)
getWindowAttrCursor WindowAttr
s = IO (Maybe Cursor) -> m (Maybe Cursor)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Cursor) -> m (Maybe Cursor))
-> IO (Maybe Cursor) -> m (Maybe Cursor)
forall a b. (a -> b) -> a -> b
$ WindowAttr
-> (Ptr WindowAttr -> IO (Maybe Cursor)) -> IO (Maybe Cursor)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO (Maybe Cursor)) -> IO (Maybe Cursor))
-> (Ptr WindowAttr -> IO (Maybe Cursor)) -> IO (Maybe Cursor)
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr Cursor
val <- Ptr (Ptr Cursor) -> IO (Ptr Cursor)
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr (Ptr Cursor)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) :: IO (Ptr Gdk.Cursor.Cursor)
Maybe Cursor
result <- Ptr Cursor -> (Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Cursor
val ((Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor))
-> (Ptr Cursor -> IO Cursor) -> IO (Maybe Cursor)
forall a b. (a -> b) -> a -> b
$ \Ptr Cursor
val' -> do
Cursor
val'' <- ((ManagedPtr Cursor -> Cursor) -> Ptr Cursor -> IO Cursor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Cursor -> Cursor
Gdk.Cursor.Cursor) Ptr Cursor
val'
Cursor -> IO Cursor
forall (m :: * -> *) a. Monad m => a -> m a
return Cursor
val''
Maybe Cursor -> IO (Maybe Cursor)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Cursor
result
setWindowAttrCursor :: MonadIO m => WindowAttr -> Ptr Gdk.Cursor.Cursor -> m ()
setWindowAttrCursor :: WindowAttr -> Ptr Cursor -> m ()
setWindowAttrCursor WindowAttr
s Ptr Cursor
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr (Ptr Cursor) -> Ptr Cursor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr (Ptr Cursor)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (Ptr Cursor
val :: Ptr Gdk.Cursor.Cursor)
clearWindowAttrCursor :: MonadIO m => WindowAttr -> m ()
clearWindowAttrCursor :: WindowAttr -> m ()
clearWindowAttrCursor WindowAttr
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr (Ptr Cursor) -> Ptr Cursor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr (Ptr Cursor)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (Ptr Cursor
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Cursor.Cursor)
#if defined(ENABLE_OVERLOADING)
data WindowAttrCursorFieldInfo
instance AttrInfo WindowAttrCursorFieldInfo where
type AttrBaseTypeConstraint WindowAttrCursorFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrCursorFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrCursorFieldInfo = (~) (Ptr Gdk.Cursor.Cursor)
type AttrTransferTypeConstraint WindowAttrCursorFieldInfo = (~)(Ptr Gdk.Cursor.Cursor)
type AttrTransferType WindowAttrCursorFieldInfo = (Ptr Gdk.Cursor.Cursor)
type AttrGetType WindowAttrCursorFieldInfo = Maybe Gdk.Cursor.Cursor
type AttrLabel WindowAttrCursorFieldInfo = "cursor"
type AttrOrigin WindowAttrCursorFieldInfo = WindowAttr
attrGet = getWindowAttrCursor
attrSet = setWindowAttrCursor
attrConstruct = undefined
attrClear = clearWindowAttrCursor
attrTransfer _ v = do
return v
windowAttr_cursor :: AttrLabelProxy "cursor"
windowAttr_cursor = AttrLabelProxy
#endif
getWindowAttrWmclassName :: MonadIO m => WindowAttr -> m (Maybe T.Text)
getWindowAttrWmclassName :: WindowAttr -> m (Maybe Text)
getWindowAttrWmclassName WindowAttr
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ WindowAttr
-> (Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) :: IO CString
Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setWindowAttrWmclassName :: MonadIO m => WindowAttr -> CString -> m ()
setWindowAttrWmclassName :: WindowAttr -> CString -> m ()
setWindowAttrWmclassName WindowAttr
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (CString
val :: CString)
clearWindowAttrWmclassName :: MonadIO m => WindowAttr -> m ()
clearWindowAttrWmclassName :: WindowAttr -> m ()
clearWindowAttrWmclassName WindowAttr
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data WindowAttrWmclassNameFieldInfo
instance AttrInfo WindowAttrWmclassNameFieldInfo where
type AttrBaseTypeConstraint WindowAttrWmclassNameFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrWmclassNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrWmclassNameFieldInfo = (~) CString
type AttrTransferTypeConstraint WindowAttrWmclassNameFieldInfo = (~)CString
type AttrTransferType WindowAttrWmclassNameFieldInfo = CString
type AttrGetType WindowAttrWmclassNameFieldInfo = Maybe T.Text
type AttrLabel WindowAttrWmclassNameFieldInfo = "wmclass_name"
type AttrOrigin WindowAttrWmclassNameFieldInfo = WindowAttr
attrGet = getWindowAttrWmclassName
attrSet = setWindowAttrWmclassName
attrConstruct = undefined
attrClear = clearWindowAttrWmclassName
attrTransfer _ v = do
return v
windowAttr_wmclassName :: AttrLabelProxy "wmclassName"
windowAttr_wmclassName = AttrLabelProxy
#endif
getWindowAttrWmclassClass :: MonadIO m => WindowAttr -> m (Maybe T.Text)
getWindowAttrWmclassClass :: WindowAttr -> m (Maybe Text)
getWindowAttrWmclassClass WindowAttr
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ WindowAttr
-> (Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr WindowAttr -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) :: IO CString
Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setWindowAttrWmclassClass :: MonadIO m => WindowAttr -> CString -> m ()
setWindowAttrWmclassClass :: WindowAttr -> CString -> m ()
setWindowAttrWmclassClass WindowAttr
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (CString
val :: CString)
clearWindowAttrWmclassClass :: MonadIO m => WindowAttr -> m ()
clearWindowAttrWmclassClass :: WindowAttr -> m ()
clearWindowAttrWmclassClass WindowAttr
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data WindowAttrWmclassClassFieldInfo
instance AttrInfo WindowAttrWmclassClassFieldInfo where
type AttrBaseTypeConstraint WindowAttrWmclassClassFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrWmclassClassFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint WindowAttrWmclassClassFieldInfo = (~) CString
type AttrTransferTypeConstraint WindowAttrWmclassClassFieldInfo = (~)CString
type AttrTransferType WindowAttrWmclassClassFieldInfo = CString
type AttrGetType WindowAttrWmclassClassFieldInfo = Maybe T.Text
type AttrLabel WindowAttrWmclassClassFieldInfo = "wmclass_class"
type AttrOrigin WindowAttrWmclassClassFieldInfo = WindowAttr
attrGet = getWindowAttrWmclassClass
attrSet = setWindowAttrWmclassClass
attrConstruct = undefined
attrClear = clearWindowAttrWmclassClass
attrTransfer _ v = do
return v
windowAttr_wmclassClass :: AttrLabelProxy "wmclassClass"
windowAttr_wmclassClass = AttrLabelProxy
#endif
getWindowAttrOverrideRedirect :: MonadIO m => WindowAttr -> m Bool
getWindowAttrOverrideRedirect :: WindowAttr -> m Bool
getWindowAttrOverrideRedirect WindowAttr
s = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO Bool) -> IO Bool
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO Bool) -> IO Bool)
-> (Ptr WindowAttr -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) :: IO CInt
let val' :: Bool
val' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
val
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
val'
setWindowAttrOverrideRedirect :: MonadIO m => WindowAttr -> Bool -> m ()
setWindowAttrOverrideRedirect :: WindowAttr -> Bool -> m ()
setWindowAttrOverrideRedirect WindowAttr
s Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
let val' :: CInt
val' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
val
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) (CInt
val' :: CInt)
#if defined(ENABLE_OVERLOADING)
data WindowAttrOverrideRedirectFieldInfo
instance AttrInfo WindowAttrOverrideRedirectFieldInfo where
type AttrBaseTypeConstraint WindowAttrOverrideRedirectFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrOverrideRedirectFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrOverrideRedirectFieldInfo = (~) Bool
type AttrTransferTypeConstraint WindowAttrOverrideRedirectFieldInfo = (~)Bool
type AttrTransferType WindowAttrOverrideRedirectFieldInfo = Bool
type AttrGetType WindowAttrOverrideRedirectFieldInfo = Bool
type AttrLabel WindowAttrOverrideRedirectFieldInfo = "override_redirect"
type AttrOrigin WindowAttrOverrideRedirectFieldInfo = WindowAttr
attrGet = getWindowAttrOverrideRedirect
attrSet = setWindowAttrOverrideRedirect
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_overrideRedirect :: AttrLabelProxy "overrideRedirect"
windowAttr_overrideRedirect = AttrLabelProxy
#endif
getWindowAttrTypeHint :: MonadIO m => WindowAttr -> m Gdk.Enums.WindowTypeHint
getWindowAttrTypeHint :: WindowAttr -> m WindowTypeHint
getWindowAttrTypeHint WindowAttr
s = IO WindowTypeHint -> m WindowTypeHint
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WindowTypeHint -> m WindowTypeHint)
-> IO WindowTypeHint -> m WindowTypeHint
forall a b. (a -> b) -> a -> b
$ WindowAttr
-> (Ptr WindowAttr -> IO WindowTypeHint) -> IO WindowTypeHint
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO WindowTypeHint) -> IO WindowTypeHint)
-> (Ptr WindowAttr -> IO WindowTypeHint) -> IO WindowTypeHint
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76) :: IO CUInt
let val' :: WindowTypeHint
val' = (Int -> WindowTypeHint
forall a. Enum a => Int -> a
toEnum (Int -> WindowTypeHint)
-> (CUInt -> Int) -> CUInt -> WindowTypeHint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
WindowTypeHint -> IO WindowTypeHint
forall (m :: * -> *) a. Monad m => a -> m a
return WindowTypeHint
val'
setWindowAttrTypeHint :: MonadIO m => WindowAttr -> Gdk.Enums.WindowTypeHint -> m ()
setWindowAttrTypeHint :: WindowAttr -> WindowTypeHint -> m ()
setWindowAttrTypeHint WindowAttr
s WindowTypeHint
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ WindowAttr -> (Ptr WindowAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr WindowAttr
s ((Ptr WindowAttr -> IO ()) -> IO ())
-> (Ptr WindowAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr WindowAttr
ptr -> do
let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (WindowTypeHint -> Int) -> WindowTypeHint -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowTypeHint -> Int
forall a. Enum a => a -> Int
fromEnum) WindowTypeHint
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr WindowAttr
ptr Ptr WindowAttr -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data WindowAttrTypeHintFieldInfo
instance AttrInfo WindowAttrTypeHintFieldInfo where
type AttrBaseTypeConstraint WindowAttrTypeHintFieldInfo = (~) WindowAttr
type AttrAllowedOps WindowAttrTypeHintFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint WindowAttrTypeHintFieldInfo = (~) Gdk.Enums.WindowTypeHint
type AttrTransferTypeConstraint WindowAttrTypeHintFieldInfo = (~)Gdk.Enums.WindowTypeHint
type AttrTransferType WindowAttrTypeHintFieldInfo = Gdk.Enums.WindowTypeHint
type AttrGetType WindowAttrTypeHintFieldInfo = Gdk.Enums.WindowTypeHint
type AttrLabel WindowAttrTypeHintFieldInfo = "type_hint"
type AttrOrigin WindowAttrTypeHintFieldInfo = WindowAttr
attrGet = getWindowAttrTypeHint
attrSet = setWindowAttrTypeHint
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
windowAttr_typeHint :: AttrLabelProxy "typeHint"
windowAttr_typeHint = AttrLabelProxy
#endif
#if defined(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 defined(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) => OL.IsLabel t (WindowAttr -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif