{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-imports #-} -- Generated code. {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# LANGUAGE ForeignFunctionInterface, ConstraintKinds, TypeFamilies, MultiParamTypeClasses, KindSignatures, FlexibleInstances, UndecidableInstances, DataKinds, OverloadedStrings, NegativeLiterals, FlexibleContexts #-} module GI.GdkAttributes where import Prelude () import Data.GI.Base.ShortPrelude import Data.Char import Data.Int import Data.Word import qualified Data.ByteString.Char8 as B import Data.ByteString.Char8 (ByteString) import qualified Data.Map as Map import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr) import Foreign.Storable (peek, poke, sizeOf) import Control.Applicative ((<$>)) import Control.Exception (onException) import Control.Monad.IO.Class import qualified Data.Text as T import Data.GI.Base.Attributes hiding (get, set) import Data.GI.Base.BasicTypes import Data.GI.Base.BasicConversions import Data.GI.Base.Closure import Data.GI.Base.GError import Data.GI.Base.GHashTable import Data.GI.Base.GParamSpec import Data.GI.Base.GVariant import Data.GI.Base.GValue import Data.GI.Base.ManagedPtr import Data.GI.Base.Overloading import Data.GI.Base.Properties hiding (new) import Data.GI.Base.Signals (SignalConnectMode(..), connectSignalFunPtr, SignalHandlerId) import Data.GI.Base.Utils import GI.Gdk -- VVV Prop "display" -- Type: TInterface "Gdk" "Display" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getAppLaunchContextDisplay :: (MonadIO m, AppLaunchContextK o) => o -> m Display getAppLaunchContextDisplay obj = liftIO $ getObjectPropertyObject obj "display" Display constructAppLaunchContextDisplay :: (DisplayK a) => a -> IO ([Char], GValue) constructAppLaunchContextDisplay val = constructObjectPropertyObject "display" val data AppLaunchContextDisplayPropertyInfo instance AttrInfo AppLaunchContextDisplayPropertyInfo where type AttrAllowedOps AppLaunchContextDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint AppLaunchContextDisplayPropertyInfo = DisplayK type AttrBaseTypeConstraint AppLaunchContextDisplayPropertyInfo = AppLaunchContextK type AttrGetType AppLaunchContextDisplayPropertyInfo = Display type AttrLabel AppLaunchContextDisplayPropertyInfo = "AppLaunchContext::display" attrGet _ = getAppLaunchContextDisplay attrSet _ = undefined attrConstruct _ = constructAppLaunchContextDisplay type instance AttributeList AppLaunchContext = '[ '("display", AppLaunchContextDisplayPropertyInfo)] -- VVV Prop "cursor-type" -- Type: TInterface "Gdk" "CursorType" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getCursorCursorType :: (MonadIO m, CursorK o) => o -> m CursorType getCursorCursorType obj = liftIO $ getObjectPropertyEnum obj "cursor-type" constructCursorCursorType :: CursorType -> IO ([Char], GValue) constructCursorCursorType val = constructObjectPropertyEnum "cursor-type" val data CursorCursorTypePropertyInfo instance AttrInfo CursorCursorTypePropertyInfo where type AttrAllowedOps CursorCursorTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint CursorCursorTypePropertyInfo = (~) CursorType type AttrBaseTypeConstraint CursorCursorTypePropertyInfo = CursorK type AttrGetType CursorCursorTypePropertyInfo = CursorType type AttrLabel CursorCursorTypePropertyInfo = "Cursor::cursor-type" attrGet _ = getCursorCursorType attrSet _ = undefined attrConstruct _ = constructCursorCursorType -- VVV Prop "display" -- Type: TInterface "Gdk" "Display" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getCursorDisplay :: (MonadIO m, CursorK o) => o -> m Display getCursorDisplay obj = liftIO $ getObjectPropertyObject obj "display" Display constructCursorDisplay :: (DisplayK a) => a -> IO ([Char], GValue) constructCursorDisplay val = constructObjectPropertyObject "display" val data CursorDisplayPropertyInfo instance AttrInfo CursorDisplayPropertyInfo where type AttrAllowedOps CursorDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint CursorDisplayPropertyInfo = DisplayK type AttrBaseTypeConstraint CursorDisplayPropertyInfo = CursorK type AttrGetType CursorDisplayPropertyInfo = Display type AttrLabel CursorDisplayPropertyInfo = "Cursor::display" attrGet _ = getCursorDisplay attrSet _ = undefined attrConstruct _ = constructCursorDisplay type instance AttributeList Cursor = '[ '("cursor-type", CursorCursorTypePropertyInfo), '("display", CursorDisplayPropertyInfo)] -- VVV Prop "associated-device" -- Type: TInterface "Gdk" "Device" -- Flags: [PropertyReadable] getDeviceAssociatedDevice :: (MonadIO m, DeviceK o) => o -> m Device getDeviceAssociatedDevice obj = liftIO $ getObjectPropertyObject obj "associated-device" Device data DeviceAssociatedDevicePropertyInfo instance AttrInfo DeviceAssociatedDevicePropertyInfo where type AttrAllowedOps DeviceAssociatedDevicePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DeviceAssociatedDevicePropertyInfo = (~) () type AttrBaseTypeConstraint DeviceAssociatedDevicePropertyInfo = DeviceK type AttrGetType DeviceAssociatedDevicePropertyInfo = Device type AttrLabel DeviceAssociatedDevicePropertyInfo = "Device::associated-device" attrGet _ = getDeviceAssociatedDevice attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "device-manager" -- Type: TInterface "Gdk" "DeviceManager" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceDeviceManager :: (MonadIO m, DeviceK o) => o -> m DeviceManager getDeviceDeviceManager obj = liftIO $ getObjectPropertyObject obj "device-manager" DeviceManager constructDeviceDeviceManager :: (DeviceManagerK a) => a -> IO ([Char], GValue) constructDeviceDeviceManager val = constructObjectPropertyObject "device-manager" val data DeviceDeviceManagerPropertyInfo instance AttrInfo DeviceDeviceManagerPropertyInfo where type AttrAllowedOps DeviceDeviceManagerPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceDeviceManagerPropertyInfo = DeviceManagerK type AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo = DeviceK type AttrGetType DeviceDeviceManagerPropertyInfo = DeviceManager type AttrLabel DeviceDeviceManagerPropertyInfo = "Device::device-manager" attrGet _ = getDeviceDeviceManager attrSet _ = undefined attrConstruct _ = constructDeviceDeviceManager -- VVV Prop "display" -- Type: TInterface "Gdk" "Display" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceDisplay :: (MonadIO m, DeviceK o) => o -> m Display getDeviceDisplay obj = liftIO $ getObjectPropertyObject obj "display" Display constructDeviceDisplay :: (DisplayK a) => a -> IO ([Char], GValue) constructDeviceDisplay val = constructObjectPropertyObject "display" val data DeviceDisplayPropertyInfo instance AttrInfo DeviceDisplayPropertyInfo where type AttrAllowedOps DeviceDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceDisplayPropertyInfo = DisplayK type AttrBaseTypeConstraint DeviceDisplayPropertyInfo = DeviceK type AttrGetType DeviceDisplayPropertyInfo = Display type AttrLabel DeviceDisplayPropertyInfo = "Device::display" attrGet _ = getDeviceDisplay attrSet _ = undefined attrConstruct _ = constructDeviceDisplay -- VVV Prop "has-cursor" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceHasCursor :: (MonadIO m, DeviceK o) => o -> m Bool getDeviceHasCursor obj = liftIO $ getObjectPropertyBool obj "has-cursor" constructDeviceHasCursor :: Bool -> IO ([Char], GValue) constructDeviceHasCursor val = constructObjectPropertyBool "has-cursor" val data DeviceHasCursorPropertyInfo instance AttrInfo DeviceHasCursorPropertyInfo where type AttrAllowedOps DeviceHasCursorPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceHasCursorPropertyInfo = (~) Bool type AttrBaseTypeConstraint DeviceHasCursorPropertyInfo = DeviceK type AttrGetType DeviceHasCursorPropertyInfo = Bool type AttrLabel DeviceHasCursorPropertyInfo = "Device::has-cursor" attrGet _ = getDeviceHasCursor attrSet _ = undefined attrConstruct _ = constructDeviceHasCursor -- VVV Prop "input-mode" -- Type: TInterface "Gdk" "InputMode" -- Flags: [PropertyReadable,PropertyWritable] getDeviceInputMode :: (MonadIO m, DeviceK o) => o -> m InputMode getDeviceInputMode obj = liftIO $ getObjectPropertyEnum obj "input-mode" setDeviceInputMode :: (MonadIO m, DeviceK o) => o -> InputMode -> m () setDeviceInputMode obj val = liftIO $ setObjectPropertyEnum obj "input-mode" val constructDeviceInputMode :: InputMode -> IO ([Char], GValue) constructDeviceInputMode val = constructObjectPropertyEnum "input-mode" val data DeviceInputModePropertyInfo instance AttrInfo DeviceInputModePropertyInfo where type AttrAllowedOps DeviceInputModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceInputModePropertyInfo = (~) InputMode type AttrBaseTypeConstraint DeviceInputModePropertyInfo = DeviceK type AttrGetType DeviceInputModePropertyInfo = InputMode type AttrLabel DeviceInputModePropertyInfo = "Device::input-mode" attrGet _ = getDeviceInputMode attrSet _ = setDeviceInputMode attrConstruct _ = constructDeviceInputMode -- VVV Prop "input-source" -- Type: TInterface "Gdk" "InputSource" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceInputSource :: (MonadIO m, DeviceK o) => o -> m InputSource getDeviceInputSource obj = liftIO $ getObjectPropertyEnum obj "input-source" constructDeviceInputSource :: InputSource -> IO ([Char], GValue) constructDeviceInputSource val = constructObjectPropertyEnum "input-source" val data DeviceInputSourcePropertyInfo instance AttrInfo DeviceInputSourcePropertyInfo where type AttrAllowedOps DeviceInputSourcePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceInputSourcePropertyInfo = (~) InputSource type AttrBaseTypeConstraint DeviceInputSourcePropertyInfo = DeviceK type AttrGetType DeviceInputSourcePropertyInfo = InputSource type AttrLabel DeviceInputSourcePropertyInfo = "Device::input-source" attrGet _ = getDeviceInputSource attrSet _ = undefined attrConstruct _ = constructDeviceInputSource -- VVV Prop "n-axes" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable] getDeviceNAxes :: (MonadIO m, DeviceK o) => o -> m Word32 getDeviceNAxes obj = liftIO $ getObjectPropertyCUInt obj "n-axes" data DeviceNAxesPropertyInfo instance AttrInfo DeviceNAxesPropertyInfo where type AttrAllowedOps DeviceNAxesPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint DeviceNAxesPropertyInfo = (~) () type AttrBaseTypeConstraint DeviceNAxesPropertyInfo = DeviceK type AttrGetType DeviceNAxesPropertyInfo = Word32 type AttrLabel DeviceNAxesPropertyInfo = "Device::n-axes" attrGet _ = getDeviceNAxes attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "name" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceName :: (MonadIO m, DeviceK o) => o -> m T.Text getDeviceName obj = liftIO $ getObjectPropertyString obj "name" constructDeviceName :: T.Text -> IO ([Char], GValue) constructDeviceName val = constructObjectPropertyString "name" val data DeviceNamePropertyInfo instance AttrInfo DeviceNamePropertyInfo where type AttrAllowedOps DeviceNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceNamePropertyInfo = (~) T.Text type AttrBaseTypeConstraint DeviceNamePropertyInfo = DeviceK type AttrGetType DeviceNamePropertyInfo = T.Text type AttrLabel DeviceNamePropertyInfo = "Device::name" attrGet _ = getDeviceName attrSet _ = undefined attrConstruct _ = constructDeviceName -- VVV Prop "product-id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceProductId :: (MonadIO m, DeviceK o) => o -> m T.Text getDeviceProductId obj = liftIO $ getObjectPropertyString obj "product-id" constructDeviceProductId :: T.Text -> IO ([Char], GValue) constructDeviceProductId val = constructObjectPropertyString "product-id" val data DeviceProductIdPropertyInfo instance AttrInfo DeviceProductIdPropertyInfo where type AttrAllowedOps DeviceProductIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceProductIdPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DeviceProductIdPropertyInfo = DeviceK type AttrGetType DeviceProductIdPropertyInfo = T.Text type AttrLabel DeviceProductIdPropertyInfo = "Device::product-id" attrGet _ = getDeviceProductId attrSet _ = undefined attrConstruct _ = constructDeviceProductId -- VVV Prop "type" -- Type: TInterface "Gdk" "DeviceType" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceType :: (MonadIO m, DeviceK o) => o -> m DeviceType getDeviceType obj = liftIO $ getObjectPropertyEnum obj "type" constructDeviceType :: DeviceType -> IO ([Char], GValue) constructDeviceType val = constructObjectPropertyEnum "type" val data DeviceTypePropertyInfo instance AttrInfo DeviceTypePropertyInfo where type AttrAllowedOps DeviceTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceTypePropertyInfo = (~) DeviceType type AttrBaseTypeConstraint DeviceTypePropertyInfo = DeviceK type AttrGetType DeviceTypePropertyInfo = DeviceType type AttrLabel DeviceTypePropertyInfo = "Device::type" attrGet _ = getDeviceType attrSet _ = undefined attrConstruct _ = constructDeviceType -- VVV Prop "vendor-id" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceVendorId :: (MonadIO m, DeviceK o) => o -> m T.Text getDeviceVendorId obj = liftIO $ getObjectPropertyString obj "vendor-id" constructDeviceVendorId :: T.Text -> IO ([Char], GValue) constructDeviceVendorId val = constructObjectPropertyString "vendor-id" val data DeviceVendorIdPropertyInfo instance AttrInfo DeviceVendorIdPropertyInfo where type AttrAllowedOps DeviceVendorIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceVendorIdPropertyInfo = (~) T.Text type AttrBaseTypeConstraint DeviceVendorIdPropertyInfo = DeviceK type AttrGetType DeviceVendorIdPropertyInfo = T.Text type AttrLabel DeviceVendorIdPropertyInfo = "Device::vendor-id" attrGet _ = getDeviceVendorId attrSet _ = undefined attrConstruct _ = constructDeviceVendorId type instance AttributeList Device = '[ '("associated-device", DeviceAssociatedDevicePropertyInfo), '("device-manager", DeviceDeviceManagerPropertyInfo), '("display", DeviceDisplayPropertyInfo), '("has-cursor", DeviceHasCursorPropertyInfo), '("input-mode", DeviceInputModePropertyInfo), '("input-source", DeviceInputSourcePropertyInfo), '("n-axes", DeviceNAxesPropertyInfo), '("name", DeviceNamePropertyInfo), '("product-id", DeviceProductIdPropertyInfo), '("type", DeviceTypePropertyInfo), '("vendor-id", DeviceVendorIdPropertyInfo)] -- VVV Prop "display" -- Type: TInterface "Gdk" "Display" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getDeviceManagerDisplay :: (MonadIO m, DeviceManagerK o) => o -> m Display getDeviceManagerDisplay obj = liftIO $ getObjectPropertyObject obj "display" Display constructDeviceManagerDisplay :: (DisplayK a) => a -> IO ([Char], GValue) constructDeviceManagerDisplay val = constructObjectPropertyObject "display" val data DeviceManagerDisplayPropertyInfo instance AttrInfo DeviceManagerDisplayPropertyInfo where type AttrAllowedOps DeviceManagerDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DeviceManagerDisplayPropertyInfo = DisplayK type AttrBaseTypeConstraint DeviceManagerDisplayPropertyInfo = DeviceManagerK type AttrGetType DeviceManagerDisplayPropertyInfo = Display type AttrLabel DeviceManagerDisplayPropertyInfo = "DeviceManager::display" attrGet _ = getDeviceManagerDisplay attrSet _ = undefined attrConstruct _ = constructDeviceManagerDisplay type instance AttributeList DeviceManager = '[ '("display", DeviceManagerDisplayPropertyInfo)] type instance AttributeList Display = '[ ] -- VVV Prop "default-display" -- Type: TInterface "Gdk" "Display" -- Flags: [PropertyReadable,PropertyWritable] getDisplayManagerDefaultDisplay :: (MonadIO m, DisplayManagerK o) => o -> m Display getDisplayManagerDefaultDisplay obj = liftIO $ getObjectPropertyObject obj "default-display" Display setDisplayManagerDefaultDisplay :: (MonadIO m, DisplayManagerK o, DisplayK a) => o -> a -> m () setDisplayManagerDefaultDisplay obj val = liftIO $ setObjectPropertyObject obj "default-display" val constructDisplayManagerDefaultDisplay :: (DisplayK a) => a -> IO ([Char], GValue) constructDisplayManagerDefaultDisplay val = constructObjectPropertyObject "default-display" val data DisplayManagerDefaultDisplayPropertyInfo instance AttrInfo DisplayManagerDefaultDisplayPropertyInfo where type AttrAllowedOps DisplayManagerDefaultDisplayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint DisplayManagerDefaultDisplayPropertyInfo = DisplayK type AttrBaseTypeConstraint DisplayManagerDefaultDisplayPropertyInfo = DisplayManagerK type AttrGetType DisplayManagerDefaultDisplayPropertyInfo = Display type AttrLabel DisplayManagerDefaultDisplayPropertyInfo = "DisplayManager::default-display" attrGet _ = getDisplayManagerDefaultDisplay attrSet _ = setDisplayManagerDefaultDisplay attrConstruct _ = constructDisplayManagerDefaultDisplay type instance AttributeList DisplayManager = '[ '("default-display", DisplayManagerDefaultDisplayPropertyInfo)] type instance AttributeList DragContext = '[ ] type instance AttributeList FrameClock = '[ ] -- VVV Prop "display" -- Type: TInterface "Gdk" "Display" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getGLContextDisplay :: (MonadIO m, GLContextK o) => o -> m Display getGLContextDisplay obj = liftIO $ getObjectPropertyObject obj "display" Display constructGLContextDisplay :: (DisplayK a) => a -> IO ([Char], GValue) constructGLContextDisplay val = constructObjectPropertyObject "display" val data GLContextDisplayPropertyInfo instance AttrInfo GLContextDisplayPropertyInfo where type AttrAllowedOps GLContextDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint GLContextDisplayPropertyInfo = DisplayK type AttrBaseTypeConstraint GLContextDisplayPropertyInfo = GLContextK type AttrGetType GLContextDisplayPropertyInfo = Display type AttrLabel GLContextDisplayPropertyInfo = "GLContext::display" attrGet _ = getGLContextDisplay attrSet _ = undefined attrConstruct _ = constructGLContextDisplay -- VVV Prop "shared-context" -- Type: TInterface "Gdk" "GLContext" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getGLContextSharedContext :: (MonadIO m, GLContextK o) => o -> m GLContext getGLContextSharedContext obj = liftIO $ getObjectPropertyObject obj "shared-context" GLContext constructGLContextSharedContext :: (GLContextK a) => a -> IO ([Char], GValue) constructGLContextSharedContext val = constructObjectPropertyObject "shared-context" val data GLContextSharedContextPropertyInfo instance AttrInfo GLContextSharedContextPropertyInfo where type AttrAllowedOps GLContextSharedContextPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint GLContextSharedContextPropertyInfo = GLContextK type AttrBaseTypeConstraint GLContextSharedContextPropertyInfo = GLContextK type AttrGetType GLContextSharedContextPropertyInfo = GLContext type AttrLabel GLContextSharedContextPropertyInfo = "GLContext::shared-context" attrGet _ = getGLContextSharedContext attrSet _ = undefined attrConstruct _ = constructGLContextSharedContext -- VVV Prop "window" -- Type: TInterface "Gdk" "Window" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getGLContextWindow :: (MonadIO m, GLContextK o) => o -> m Window getGLContextWindow obj = liftIO $ getObjectPropertyObject obj "window" Window constructGLContextWindow :: (WindowK a) => a -> IO ([Char], GValue) constructGLContextWindow val = constructObjectPropertyObject "window" val data GLContextWindowPropertyInfo instance AttrInfo GLContextWindowPropertyInfo where type AttrAllowedOps GLContextWindowPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint GLContextWindowPropertyInfo = WindowK type AttrBaseTypeConstraint GLContextWindowPropertyInfo = GLContextK type AttrGetType GLContextWindowPropertyInfo = Window type AttrLabel GLContextWindowPropertyInfo = "GLContext::window" attrGet _ = getGLContextWindow attrSet _ = undefined attrConstruct _ = constructGLContextWindow type instance AttributeList GLContext = '[ '("display", GLContextDisplayPropertyInfo), '("shared-context", GLContextSharedContextPropertyInfo), '("window", GLContextWindowPropertyInfo)] type instance AttributeList Keymap = '[ ] -- VVV Prop "font-options" -- Type: TBasicType TVoid -- Flags: [PropertyReadable,PropertyWritable] getScreenFontOptions :: (MonadIO m, ScreenK o) => o -> m (Ptr ()) getScreenFontOptions obj = liftIO $ getObjectPropertyPtr obj "font-options" setScreenFontOptions :: (MonadIO m, ScreenK o) => o -> (Ptr ()) -> m () setScreenFontOptions obj val = liftIO $ setObjectPropertyPtr obj "font-options" val constructScreenFontOptions :: (Ptr ()) -> IO ([Char], GValue) constructScreenFontOptions val = constructObjectPropertyPtr "font-options" val data ScreenFontOptionsPropertyInfo instance AttrInfo ScreenFontOptionsPropertyInfo where type AttrAllowedOps ScreenFontOptionsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint ScreenFontOptionsPropertyInfo = (~) (Ptr ()) type AttrBaseTypeConstraint ScreenFontOptionsPropertyInfo = ScreenK type AttrGetType ScreenFontOptionsPropertyInfo = (Ptr ()) type AttrLabel ScreenFontOptionsPropertyInfo = "Screen::font-options" attrGet _ = getScreenFontOptions attrSet _ = setScreenFontOptions attrConstruct _ = constructScreenFontOptions -- VVV Prop "resolution" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getScreenResolution :: (MonadIO m, ScreenK o) => o -> m Double getScreenResolution obj = liftIO $ getObjectPropertyDouble obj "resolution" setScreenResolution :: (MonadIO m, ScreenK o) => o -> Double -> m () setScreenResolution obj val = liftIO $ setObjectPropertyDouble obj "resolution" val constructScreenResolution :: Double -> IO ([Char], GValue) constructScreenResolution val = constructObjectPropertyDouble "resolution" val data ScreenResolutionPropertyInfo instance AttrInfo ScreenResolutionPropertyInfo where type AttrAllowedOps ScreenResolutionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint ScreenResolutionPropertyInfo = (~) Double type AttrBaseTypeConstraint ScreenResolutionPropertyInfo = ScreenK type AttrGetType ScreenResolutionPropertyInfo = Double type AttrLabel ScreenResolutionPropertyInfo = "Screen::resolution" attrGet _ = getScreenResolution attrSet _ = setScreenResolution attrConstruct _ = constructScreenResolution type instance AttributeList Screen = '[ '("font-options", ScreenFontOptionsPropertyInfo), '("resolution", ScreenResolutionPropertyInfo)] type instance AttributeList Visual = '[ ] -- VVV Prop "cursor" -- Type: TInterface "Gdk" "Cursor" -- Flags: [PropertyReadable,PropertyWritable] getWindowCursor :: (MonadIO m, WindowK o) => o -> m Cursor getWindowCursor obj = liftIO $ getObjectPropertyObject obj "cursor" Cursor setWindowCursor :: (MonadIO m, WindowK o, CursorK a) => o -> a -> m () setWindowCursor obj val = liftIO $ setObjectPropertyObject obj "cursor" val constructWindowCursor :: (CursorK a) => a -> IO ([Char], GValue) constructWindowCursor val = constructObjectPropertyObject "cursor" val data WindowCursorPropertyInfo instance AttrInfo WindowCursorPropertyInfo where type AttrAllowedOps WindowCursorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint WindowCursorPropertyInfo = CursorK type AttrBaseTypeConstraint WindowCursorPropertyInfo = WindowK type AttrGetType WindowCursorPropertyInfo = Cursor type AttrLabel WindowCursorPropertyInfo = "Window::cursor" attrGet _ = getWindowCursor attrSet _ = setWindowCursor attrConstruct _ = constructWindowCursor type instance AttributeList Window = '[ '("cursor", WindowCursorPropertyInfo)]