{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @ClutterSettings@ is an opaque structure whose
-- members cannot be directly accessed.
-- 
-- /Since: 1.4/

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Clutter.Objects.Settings
    ( 

-- * Exported types
    Settings(..)                            ,
    IsSettings                              ,
    toSettings                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveSettingsMethod                   ,
#endif

-- ** getDefault #method:getDefault#

    settingsGetDefault                      ,




 -- * Properties


-- ** backend #attr:backend#
-- | A back pointer to the t'GI.Clutter.Objects.Backend.Backend'
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsBackendPropertyInfo             ,
#endif
    constructSettingsBackend                ,
#if defined(ENABLE_OVERLOADING)
    settingsBackend                         ,
#endif


-- ** dndDragThreshold #attr:dndDragThreshold#
-- | The default distance that the cursor of a pointer device
-- should travel before a drag operation should start.
-- 
-- /Since: 1.8/

#if defined(ENABLE_OVERLOADING)
    SettingsDndDragThresholdPropertyInfo    ,
#endif
    constructSettingsDndDragThreshold       ,
    getSettingsDndDragThreshold             ,
    setSettingsDndDragThreshold             ,
#if defined(ENABLE_OVERLOADING)
    settingsDndDragThreshold                ,
#endif


-- ** doubleClickDistance #attr:doubleClickDistance#
-- | The maximum distance, in pixels, between button-press events that
-- determines whether or not to increase the click count by 1.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsDoubleClickDistancePropertyInfo ,
#endif
    constructSettingsDoubleClickDistance    ,
    getSettingsDoubleClickDistance          ,
    setSettingsDoubleClickDistance          ,
#if defined(ENABLE_OVERLOADING)
    settingsDoubleClickDistance             ,
#endif


-- ** doubleClickTime #attr:doubleClickTime#
-- | The time, in milliseconds, that should elapse between button-press
-- events in order to increase the click count by 1.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsDoubleClickTimePropertyInfo     ,
#endif
    constructSettingsDoubleClickTime        ,
    getSettingsDoubleClickTime              ,
    setSettingsDoubleClickTime              ,
#if defined(ENABLE_OVERLOADING)
    settingsDoubleClickTime                 ,
#endif


-- ** fontAntialias #attr:fontAntialias#
-- | Whether or not to use antialiasing when rendering text; a value
-- of 1 enables it unconditionally; a value of 0 disables it
-- unconditionally; and -1 will use the system\'s default.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsFontAntialiasPropertyInfo       ,
#endif
    constructSettingsFontAntialias          ,
    getSettingsFontAntialias                ,
    setSettingsFontAntialias                ,
#if defined(ENABLE_OVERLOADING)
    settingsFontAntialias                   ,
#endif


-- ** fontDpi #attr:fontDpi#
-- | The DPI used when rendering text, as a value of 1024 * dots\/inch.
-- 
-- If set to -1, the system\'s default will be used instead
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsFontDpiPropertyInfo             ,
#endif
    constructSettingsFontDpi                ,
    getSettingsFontDpi                      ,
    setSettingsFontDpi                      ,
#if defined(ENABLE_OVERLOADING)
    settingsFontDpi                         ,
#endif


-- ** fontHintStyle #attr:fontHintStyle#
-- | The style of the hinting used when rendering text. Valid values
-- are:
-- 
--   - hintnone
--   - hintslight
--   - hintmedium
--   - hintfull
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsFontHintStylePropertyInfo       ,
#endif
    clearSettingsFontHintStyle              ,
    constructSettingsFontHintStyle          ,
    getSettingsFontHintStyle                ,
    setSettingsFontHintStyle                ,
#if defined(ENABLE_OVERLOADING)
    settingsFontHintStyle                   ,
#endif


-- ** fontHinting #attr:fontHinting#
-- | Whether or not to use hinting when rendering text; a value of 1
-- unconditionally enables it; a value of 0 unconditionally disables
-- it; and a value of -1 will use the system\'s default.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsFontHintingPropertyInfo         ,
#endif
    constructSettingsFontHinting            ,
    getSettingsFontHinting                  ,
    setSettingsFontHinting                  ,
#if defined(ENABLE_OVERLOADING)
    settingsFontHinting                     ,
#endif


-- ** fontName #attr:fontName#
-- | The default font name that should be used by text actors, as
-- a string that can be passed to 'GI.Pango.Functions.fontDescriptionFromString'.
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsFontNamePropertyInfo            ,
#endif
    clearSettingsFontName                   ,
    constructSettingsFontName               ,
    getSettingsFontName                     ,
    setSettingsFontName                     ,
#if defined(ENABLE_OVERLOADING)
    settingsFontName                        ,
#endif


-- ** fontSubpixelOrder #attr:fontSubpixelOrder#
-- | The type of sub-pixel antialiasing used when rendering text. Valid
-- values are:
-- 
--   - none
--   - rgb
--   - bgr
--   - vrgb
--   - vbgr
-- 
-- /Since: 1.4/

#if defined(ENABLE_OVERLOADING)
    SettingsFontSubpixelOrderPropertyInfo   ,
#endif
    clearSettingsFontSubpixelOrder          ,
    constructSettingsFontSubpixelOrder      ,
    getSettingsFontSubpixelOrder            ,
    setSettingsFontSubpixelOrder            ,
#if defined(ENABLE_OVERLOADING)
    settingsFontSubpixelOrder               ,
#endif


-- ** fontconfigTimestamp #attr:fontconfigTimestamp#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SettingsFontconfigTimestampPropertyInfo ,
#endif
    constructSettingsFontconfigTimestamp    ,
    setSettingsFontconfigTimestamp          ,
#if defined(ENABLE_OVERLOADING)
    settingsFontconfigTimestamp             ,
#endif


-- ** longPressDuration #attr:longPressDuration#
-- | Sets the minimum duration for a press to be recognized as a long press
-- gesture. The duration is expressed in milliseconds.
-- 
-- See also [ClickAction:longPressDuration]("GI.Clutter.Objects.ClickAction#g:attr:longPressDuration").
-- 
-- /Since: 1.8/

#if defined(ENABLE_OVERLOADING)
    SettingsLongPressDurationPropertyInfo   ,
#endif
    constructSettingsLongPressDuration      ,
    getSettingsLongPressDuration            ,
    setSettingsLongPressDuration            ,
#if defined(ENABLE_OVERLOADING)
    settingsLongPressDuration               ,
#endif


-- ** passwordHintTime #attr:passwordHintTime#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SettingsPasswordHintTimePropertyInfo    ,
#endif
    constructSettingsPasswordHintTime       ,
    getSettingsPasswordHintTime             ,
    setSettingsPasswordHintTime             ,
#if defined(ENABLE_OVERLOADING)
    settingsPasswordHintTime                ,
#endif


-- ** unscaledFontDpi #attr:unscaledFontDpi#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SettingsUnscaledFontDpiPropertyInfo     ,
#endif
    constructSettingsUnscaledFontDpi        ,
    setSettingsUnscaledFontDpi              ,
#if defined(ENABLE_OVERLOADING)
    settingsUnscaledFontDpi                 ,
#endif


-- ** windowScalingFactor #attr:windowScalingFactor#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SettingsWindowScalingFactorPropertyInfo ,
#endif
    constructSettingsWindowScalingFactor    ,
    getSettingsWindowScalingFactor          ,
    setSettingsWindowScalingFactor          ,
#if defined(ENABLE_OVERLOADING)
    settingsWindowScalingFactor             ,
#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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
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 qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.Clutter.Objects.Backend as Clutter.Backend
import qualified GI.GObject.Objects.Object as GObject.Object

-- | Memory-managed wrapper type.
newtype Settings = Settings (SP.ManagedPtr Settings)
    deriving (Settings -> Settings -> Bool
(Settings -> Settings -> Bool)
-> (Settings -> Settings -> Bool) -> Eq Settings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Settings -> Settings -> Bool
== :: Settings -> Settings -> Bool
$c/= :: Settings -> Settings -> Bool
/= :: Settings -> Settings -> Bool
Eq)

instance SP.ManagedPtrNewtype Settings where
    toManagedPtr :: Settings -> ManagedPtr Settings
toManagedPtr (Settings ManagedPtr Settings
p) = ManagedPtr Settings
p

foreign import ccall "clutter_settings_get_type"
    c_clutter_settings_get_type :: IO B.Types.GType

instance B.Types.TypedObject Settings where
    glibType :: IO GType
glibType = IO GType
c_clutter_settings_get_type

instance B.Types.GObject Settings

-- | Type class for types which can be safely cast to `Settings`, for instance with `toSettings`.
class (SP.GObject o, O.IsDescendantOf Settings o) => IsSettings o
instance (SP.GObject o, O.IsDescendantOf Settings o) => IsSettings o

instance O.HasParentTypes Settings
type instance O.ParentTypes Settings = '[GObject.Object.Object]

-- | Cast to `Settings`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toSettings :: (MIO.MonadIO m, IsSettings o) => o -> m Settings
toSettings :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> m Settings
toSettings = IO Settings -> m Settings
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Settings -> m Settings)
-> (o -> IO Settings) -> o -> m Settings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Settings -> Settings) -> o -> IO Settings
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Settings -> Settings
Settings

-- | Convert 'Settings' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Settings) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_settings_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Settings -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Settings
P.Nothing = Ptr GValue -> Ptr Settings -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Settings
forall a. Ptr a
FP.nullPtr :: FP.Ptr Settings)
    gvalueSet_ Ptr GValue
gv (P.Just Settings
obj) = Settings -> (Ptr Settings -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Settings
obj (Ptr GValue -> Ptr Settings -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Settings)
gvalueGet_ Ptr GValue
gv = do
        Ptr Settings
ptr <- Ptr GValue -> IO (Ptr Settings)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Settings)
        if Ptr Settings
ptr Ptr Settings -> Ptr Settings -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Settings
forall a. Ptr a
FP.nullPtr
        then Settings -> Maybe Settings
forall a. a -> Maybe a
P.Just (Settings -> Maybe Settings) -> IO Settings -> IO (Maybe Settings)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Settings -> Settings) -> Ptr Settings -> IO Settings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Settings -> Settings
Settings Ptr Settings
ptr
        else Maybe Settings -> IO (Maybe Settings)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Settings
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveSettingsMethod (t :: Symbol) (o :: *) :: * where
    ResolveSettingsMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSettingsMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSettingsMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSettingsMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSettingsMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSettingsMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSettingsMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSettingsMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSettingsMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSettingsMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSettingsMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSettingsMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSettingsMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSettingsMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSettingsMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSettingsMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSettingsMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSettingsMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingsMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingsMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingsMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingsMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingsMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveSettingsMethod t Settings, O.OverloadedMethod info Settings p) => OL.IsLabel t (Settings -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveSettingsMethod t Settings, O.OverloadedMethod info Settings p, R.HasField t Settings p) => R.HasField t Settings p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveSettingsMethod t Settings, O.OverloadedMethodInfo info Settings) => OL.IsLabel t (O.MethodProxy info Settings) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "backend"
   -- Type: TInterface (Name {namespace = "Clutter", name = "Backend"})
   -- Flags: [PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Construct a `GValueConstruct` with valid value for the “@backend@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsBackend :: (IsSettings o, MIO.MonadIO m, Clutter.Backend.IsBackend a) => a -> m (GValueConstruct o)
constructSettingsBackend :: forall o (m :: * -> *) a.
(IsSettings o, MonadIO m, IsBackend a) =>
a -> m (GValueConstruct o)
constructSettingsBackend a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"backend" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data SettingsBackendPropertyInfo
instance AttrInfo SettingsBackendPropertyInfo where
    type AttrAllowedOps SettingsBackendPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint SettingsBackendPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsBackendPropertyInfo = Clutter.Backend.IsBackend
    type AttrTransferTypeConstraint SettingsBackendPropertyInfo = Clutter.Backend.IsBackend
    type AttrTransferType SettingsBackendPropertyInfo = Clutter.Backend.Backend
    type AttrGetType SettingsBackendPropertyInfo = ()
    type AttrLabel SettingsBackendPropertyInfo = "backend"
    type AttrOrigin SettingsBackendPropertyInfo = Settings
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Clutter.Backend.Backend v
    attrConstruct = constructSettingsBackend
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.backend"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:backend"
        })
#endif

-- VVV Prop "dnd-drag-threshold"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@dnd-drag-threshold@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #dndDragThreshold
-- @
getSettingsDndDragThreshold :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsDndDragThreshold :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Int32
getSettingsDndDragThreshold o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"dnd-drag-threshold"

-- | Set the value of the “@dnd-drag-threshold@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #dndDragThreshold 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsDndDragThreshold :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsDndDragThreshold :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsDndDragThreshold o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"dnd-drag-threshold" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@dnd-drag-threshold@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsDndDragThreshold :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsDndDragThreshold :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsDndDragThreshold Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"dnd-drag-threshold" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsDndDragThresholdPropertyInfo
instance AttrInfo SettingsDndDragThresholdPropertyInfo where
    type AttrAllowedOps SettingsDndDragThresholdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsDndDragThresholdPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsDndDragThresholdPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsDndDragThresholdPropertyInfo = (~) Int32
    type AttrTransferType SettingsDndDragThresholdPropertyInfo = Int32
    type AttrGetType SettingsDndDragThresholdPropertyInfo = Int32
    type AttrLabel SettingsDndDragThresholdPropertyInfo = "dnd-drag-threshold"
    type AttrOrigin SettingsDndDragThresholdPropertyInfo = Settings
    attrGet = getSettingsDndDragThreshold
    attrSet = setSettingsDndDragThreshold
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsDndDragThreshold
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.dndDragThreshold"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:dndDragThreshold"
        })
#endif

-- VVV Prop "double-click-distance"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@double-click-distance@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #doubleClickDistance
-- @
getSettingsDoubleClickDistance :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsDoubleClickDistance :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Int32
getSettingsDoubleClickDistance o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"double-click-distance"

-- | Set the value of the “@double-click-distance@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #doubleClickDistance 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsDoubleClickDistance :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsDoubleClickDistance :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsDoubleClickDistance o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"double-click-distance" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@double-click-distance@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsDoubleClickDistance :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsDoubleClickDistance :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsDoubleClickDistance Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"double-click-distance" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsDoubleClickDistancePropertyInfo
instance AttrInfo SettingsDoubleClickDistancePropertyInfo where
    type AttrAllowedOps SettingsDoubleClickDistancePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsDoubleClickDistancePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsDoubleClickDistancePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsDoubleClickDistancePropertyInfo = (~) Int32
    type AttrTransferType SettingsDoubleClickDistancePropertyInfo = Int32
    type AttrGetType SettingsDoubleClickDistancePropertyInfo = Int32
    type AttrLabel SettingsDoubleClickDistancePropertyInfo = "double-click-distance"
    type AttrOrigin SettingsDoubleClickDistancePropertyInfo = Settings
    attrGet = getSettingsDoubleClickDistance
    attrSet = setSettingsDoubleClickDistance
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsDoubleClickDistance
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.doubleClickDistance"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:doubleClickDistance"
        })
#endif

-- VVV Prop "double-click-time"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@double-click-time@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #doubleClickTime
-- @
getSettingsDoubleClickTime :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsDoubleClickTime :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Int32
getSettingsDoubleClickTime o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"double-click-time"

-- | Set the value of the “@double-click-time@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #doubleClickTime 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsDoubleClickTime :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsDoubleClickTime :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsDoubleClickTime o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"double-click-time" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@double-click-time@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsDoubleClickTime :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsDoubleClickTime :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsDoubleClickTime Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"double-click-time" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsDoubleClickTimePropertyInfo
instance AttrInfo SettingsDoubleClickTimePropertyInfo where
    type AttrAllowedOps SettingsDoubleClickTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsDoubleClickTimePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsDoubleClickTimePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsDoubleClickTimePropertyInfo = (~) Int32
    type AttrTransferType SettingsDoubleClickTimePropertyInfo = Int32
    type AttrGetType SettingsDoubleClickTimePropertyInfo = Int32
    type AttrLabel SettingsDoubleClickTimePropertyInfo = "double-click-time"
    type AttrOrigin SettingsDoubleClickTimePropertyInfo = Settings
    attrGet = getSettingsDoubleClickTime
    attrSet = setSettingsDoubleClickTime
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsDoubleClickTime
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.doubleClickTime"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:doubleClickTime"
        })
#endif

-- VVV Prop "font-antialias"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@font-antialias@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #fontAntialias
-- @
getSettingsFontAntialias :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsFontAntialias :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Int32
getSettingsFontAntialias o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"font-antialias"

-- | Set the value of the “@font-antialias@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #fontAntialias 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsFontAntialias :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsFontAntialias :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsFontAntialias o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"font-antialias" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@font-antialias@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsFontAntialias :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsFontAntialias :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsFontAntialias Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"font-antialias" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsFontAntialiasPropertyInfo
instance AttrInfo SettingsFontAntialiasPropertyInfo where
    type AttrAllowedOps SettingsFontAntialiasPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsFontAntialiasPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsFontAntialiasPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsFontAntialiasPropertyInfo = (~) Int32
    type AttrTransferType SettingsFontAntialiasPropertyInfo = Int32
    type AttrGetType SettingsFontAntialiasPropertyInfo = Int32
    type AttrLabel SettingsFontAntialiasPropertyInfo = "font-antialias"
    type AttrOrigin SettingsFontAntialiasPropertyInfo = Settings
    attrGet = getSettingsFontAntialias
    attrSet = setSettingsFontAntialias
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsFontAntialias
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.fontAntialias"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:fontAntialias"
        })
#endif

-- VVV Prop "font-dpi"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@font-dpi@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #fontDpi
-- @
getSettingsFontDpi :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsFontDpi :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Int32
getSettingsFontDpi o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"font-dpi"

-- | Set the value of the “@font-dpi@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #fontDpi 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsFontDpi :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsFontDpi :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsFontDpi o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"font-dpi" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@font-dpi@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsFontDpi :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsFontDpi :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsFontDpi Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"font-dpi" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsFontDpiPropertyInfo
instance AttrInfo SettingsFontDpiPropertyInfo where
    type AttrAllowedOps SettingsFontDpiPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsFontDpiPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsFontDpiPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsFontDpiPropertyInfo = (~) Int32
    type AttrTransferType SettingsFontDpiPropertyInfo = Int32
    type AttrGetType SettingsFontDpiPropertyInfo = Int32
    type AttrLabel SettingsFontDpiPropertyInfo = "font-dpi"
    type AttrOrigin SettingsFontDpiPropertyInfo = Settings
    attrGet = getSettingsFontDpi
    attrSet = setSettingsFontDpi
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsFontDpi
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.fontDpi"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:fontDpi"
        })
#endif

-- VVV Prop "font-hint-style"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@font-hint-style@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #fontHintStyle
-- @
getSettingsFontHintStyle :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsFontHintStyle :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> m (Maybe Text)
getSettingsFontHintStyle o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"font-hint-style"

-- | Set the value of the “@font-hint-style@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #fontHintStyle 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsFontHintStyle :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsFontHintStyle :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Text -> m ()
setSettingsFontHintStyle o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"font-hint-style" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@font-hint-style@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsFontHintStyle :: (IsSettings o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingsFontHintStyle :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingsFontHintStyle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"font-hint-style" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@font-hint-style@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #fontHintStyle
-- @
clearSettingsFontHintStyle :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsFontHintStyle :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m ()
clearSettingsFontHintStyle o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"font-hint-style" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsFontHintStylePropertyInfo
instance AttrInfo SettingsFontHintStylePropertyInfo where
    type AttrAllowedOps SettingsFontHintStylePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsFontHintStylePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsFontHintStylePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsFontHintStylePropertyInfo = (~) T.Text
    type AttrTransferType SettingsFontHintStylePropertyInfo = T.Text
    type AttrGetType SettingsFontHintStylePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsFontHintStylePropertyInfo = "font-hint-style"
    type AttrOrigin SettingsFontHintStylePropertyInfo = Settings
    attrGet = getSettingsFontHintStyle
    attrSet = setSettingsFontHintStyle
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsFontHintStyle
    attrClear = clearSettingsFontHintStyle
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.fontHintStyle"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:fontHintStyle"
        })
#endif

-- VVV Prop "font-hinting"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@font-hinting@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #fontHinting
-- @
getSettingsFontHinting :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsFontHinting :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Int32
getSettingsFontHinting o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"font-hinting"

-- | Set the value of the “@font-hinting@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #fontHinting 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsFontHinting :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsFontHinting :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsFontHinting o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"font-hinting" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@font-hinting@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsFontHinting :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsFontHinting :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsFontHinting Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"font-hinting" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsFontHintingPropertyInfo
instance AttrInfo SettingsFontHintingPropertyInfo where
    type AttrAllowedOps SettingsFontHintingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsFontHintingPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsFontHintingPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsFontHintingPropertyInfo = (~) Int32
    type AttrTransferType SettingsFontHintingPropertyInfo = Int32
    type AttrGetType SettingsFontHintingPropertyInfo = Int32
    type AttrLabel SettingsFontHintingPropertyInfo = "font-hinting"
    type AttrOrigin SettingsFontHintingPropertyInfo = Settings
    attrGet = getSettingsFontHinting
    attrSet = setSettingsFontHinting
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsFontHinting
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.fontHinting"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:fontHinting"
        })
#endif

-- VVV Prop "font-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@font-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #fontName
-- @
getSettingsFontName :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsFontName :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> m (Maybe Text)
getSettingsFontName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"font-name"

-- | Set the value of the “@font-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #fontName 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsFontName :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsFontName :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Text -> m ()
setSettingsFontName o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"font-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@font-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsFontName :: (IsSettings o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingsFontName :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingsFontName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"font-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@font-name@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #fontName
-- @
clearSettingsFontName :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsFontName :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m ()
clearSettingsFontName o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"font-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsFontNamePropertyInfo
instance AttrInfo SettingsFontNamePropertyInfo where
    type AttrAllowedOps SettingsFontNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsFontNamePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsFontNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsFontNamePropertyInfo = (~) T.Text
    type AttrTransferType SettingsFontNamePropertyInfo = T.Text
    type AttrGetType SettingsFontNamePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsFontNamePropertyInfo = "font-name"
    type AttrOrigin SettingsFontNamePropertyInfo = Settings
    attrGet = getSettingsFontName
    attrSet = setSettingsFontName
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsFontName
    attrClear = clearSettingsFontName
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.fontName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:fontName"
        })
#endif

-- VVV Prop "font-subpixel-order"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@font-subpixel-order@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #fontSubpixelOrder
-- @
getSettingsFontSubpixelOrder :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsFontSubpixelOrder :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> m (Maybe Text)
getSettingsFontSubpixelOrder o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"font-subpixel-order"

-- | Set the value of the “@font-subpixel-order@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #fontSubpixelOrder 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsFontSubpixelOrder :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsFontSubpixelOrder :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Text -> m ()
setSettingsFontSubpixelOrder o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"font-subpixel-order" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@font-subpixel-order@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsFontSubpixelOrder :: (IsSettings o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingsFontSubpixelOrder :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingsFontSubpixelOrder Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"font-subpixel-order" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@font-subpixel-order@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #fontSubpixelOrder
-- @
clearSettingsFontSubpixelOrder :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsFontSubpixelOrder :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m ()
clearSettingsFontSubpixelOrder o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"font-subpixel-order" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsFontSubpixelOrderPropertyInfo
instance AttrInfo SettingsFontSubpixelOrderPropertyInfo where
    type AttrAllowedOps SettingsFontSubpixelOrderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsFontSubpixelOrderPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsFontSubpixelOrderPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsFontSubpixelOrderPropertyInfo = (~) T.Text
    type AttrTransferType SettingsFontSubpixelOrderPropertyInfo = T.Text
    type AttrGetType SettingsFontSubpixelOrderPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsFontSubpixelOrderPropertyInfo = "font-subpixel-order"
    type AttrOrigin SettingsFontSubpixelOrderPropertyInfo = Settings
    attrGet = getSettingsFontSubpixelOrder
    attrSet = setSettingsFontSubpixelOrder
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsFontSubpixelOrder
    attrClear = clearSettingsFontSubpixelOrder
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.fontSubpixelOrder"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:fontSubpixelOrder"
        })
#endif

-- VVV Prop "fontconfig-timestamp"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Set the value of the “@fontconfig-timestamp@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #fontconfigTimestamp 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsFontconfigTimestamp :: (MonadIO m, IsSettings o) => o -> Word32 -> m ()
setSettingsFontconfigTimestamp :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Word32 -> m ()
setSettingsFontconfigTimestamp o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"fontconfig-timestamp" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@fontconfig-timestamp@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsFontconfigTimestamp :: (IsSettings o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingsFontconfigTimestamp :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingsFontconfigTimestamp Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"fontconfig-timestamp" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingsFontconfigTimestampPropertyInfo
instance AttrInfo SettingsFontconfigTimestampPropertyInfo where
    type AttrAllowedOps SettingsFontconfigTimestampPropertyInfo = '[ 'AttrSet, 'AttrConstruct]
    type AttrBaseTypeConstraint SettingsFontconfigTimestampPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsFontconfigTimestampPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingsFontconfigTimestampPropertyInfo = (~) Word32
    type AttrTransferType SettingsFontconfigTimestampPropertyInfo = Word32
    type AttrGetType SettingsFontconfigTimestampPropertyInfo = ()
    type AttrLabel SettingsFontconfigTimestampPropertyInfo = "fontconfig-timestamp"
    type AttrOrigin SettingsFontconfigTimestampPropertyInfo = Settings
    attrGet = undefined
    attrSet = setSettingsFontconfigTimestamp
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsFontconfigTimestamp
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.fontconfigTimestamp"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:fontconfigTimestamp"
        })
#endif

-- VVV Prop "long-press-duration"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@long-press-duration@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #longPressDuration
-- @
getSettingsLongPressDuration :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsLongPressDuration :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Int32
getSettingsLongPressDuration o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"long-press-duration"

-- | Set the value of the “@long-press-duration@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #longPressDuration 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsLongPressDuration :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsLongPressDuration :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsLongPressDuration o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"long-press-duration" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@long-press-duration@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsLongPressDuration :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsLongPressDuration :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsLongPressDuration Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"long-press-duration" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsLongPressDurationPropertyInfo
instance AttrInfo SettingsLongPressDurationPropertyInfo where
    type AttrAllowedOps SettingsLongPressDurationPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsLongPressDurationPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsLongPressDurationPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsLongPressDurationPropertyInfo = (~) Int32
    type AttrTransferType SettingsLongPressDurationPropertyInfo = Int32
    type AttrGetType SettingsLongPressDurationPropertyInfo = Int32
    type AttrLabel SettingsLongPressDurationPropertyInfo = "long-press-duration"
    type AttrOrigin SettingsLongPressDurationPropertyInfo = Settings
    attrGet = getSettingsLongPressDuration
    attrSet = setSettingsLongPressDuration
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsLongPressDuration
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.longPressDuration"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:longPressDuration"
        })
#endif

-- VVV Prop "password-hint-time"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@password-hint-time@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #passwordHintTime
-- @
getSettingsPasswordHintTime :: (MonadIO m, IsSettings o) => o -> m Word32
getSettingsPasswordHintTime :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Word32
getSettingsPasswordHintTime o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"password-hint-time"

-- | Set the value of the “@password-hint-time@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #passwordHintTime 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsPasswordHintTime :: (MonadIO m, IsSettings o) => o -> Word32 -> m ()
setSettingsPasswordHintTime :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Word32 -> m ()
setSettingsPasswordHintTime o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"password-hint-time" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@password-hint-time@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsPasswordHintTime :: (IsSettings o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructSettingsPasswordHintTime :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructSettingsPasswordHintTime Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"password-hint-time" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingsPasswordHintTimePropertyInfo
instance AttrInfo SettingsPasswordHintTimePropertyInfo where
    type AttrAllowedOps SettingsPasswordHintTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsPasswordHintTimePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsPasswordHintTimePropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingsPasswordHintTimePropertyInfo = (~) Word32
    type AttrTransferType SettingsPasswordHintTimePropertyInfo = Word32
    type AttrGetType SettingsPasswordHintTimePropertyInfo = Word32
    type AttrLabel SettingsPasswordHintTimePropertyInfo = "password-hint-time"
    type AttrOrigin SettingsPasswordHintTimePropertyInfo = Settings
    attrGet = getSettingsPasswordHintTime
    attrSet = setSettingsPasswordHintTime
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsPasswordHintTime
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.passwordHintTime"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:passwordHintTime"
        })
#endif

-- VVV Prop "unscaled-font-dpi"
   -- Type: TBasicType TInt
   -- Flags: [PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Set the value of the “@unscaled-font-dpi@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #unscaledFontDpi 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsUnscaledFontDpi :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsUnscaledFontDpi :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsUnscaledFontDpi o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"unscaled-font-dpi" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@unscaled-font-dpi@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsUnscaledFontDpi :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsUnscaledFontDpi :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsUnscaledFontDpi Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"unscaled-font-dpi" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsUnscaledFontDpiPropertyInfo
instance AttrInfo SettingsUnscaledFontDpiPropertyInfo where
    type AttrAllowedOps SettingsUnscaledFontDpiPropertyInfo = '[ 'AttrSet, 'AttrConstruct]
    type AttrBaseTypeConstraint SettingsUnscaledFontDpiPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsUnscaledFontDpiPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsUnscaledFontDpiPropertyInfo = (~) Int32
    type AttrTransferType SettingsUnscaledFontDpiPropertyInfo = Int32
    type AttrGetType SettingsUnscaledFontDpiPropertyInfo = ()
    type AttrLabel SettingsUnscaledFontDpiPropertyInfo = "unscaled-font-dpi"
    type AttrOrigin SettingsUnscaledFontDpiPropertyInfo = Settings
    attrGet = undefined
    attrSet = setSettingsUnscaledFontDpi
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsUnscaledFontDpi
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.unscaledFontDpi"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:unscaledFontDpi"
        })
#endif

-- VVV Prop "window-scaling-factor"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@window-scaling-factor@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #windowScalingFactor
-- @
getSettingsWindowScalingFactor :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsWindowScalingFactor :: forall (m :: * -> *) o. (MonadIO m, IsSettings o) => o -> m Int32
getSettingsWindowScalingFactor o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"window-scaling-factor"

-- | Set the value of the “@window-scaling-factor@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #windowScalingFactor 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsWindowScalingFactor :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsWindowScalingFactor :: forall (m :: * -> *) o.
(MonadIO m, IsSettings o) =>
o -> Int32 -> m ()
setSettingsWindowScalingFactor o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"window-scaling-factor" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@window-scaling-factor@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsWindowScalingFactor :: (IsSettings o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructSettingsWindowScalingFactor :: forall o (m :: * -> *).
(IsSettings o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructSettingsWindowScalingFactor Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"window-scaling-factor" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsWindowScalingFactorPropertyInfo
instance AttrInfo SettingsWindowScalingFactorPropertyInfo where
    type AttrAllowedOps SettingsWindowScalingFactorPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsWindowScalingFactorPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsWindowScalingFactorPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsWindowScalingFactorPropertyInfo = (~) Int32
    type AttrTransferType SettingsWindowScalingFactorPropertyInfo = Int32
    type AttrGetType SettingsWindowScalingFactorPropertyInfo = Int32
    type AttrLabel SettingsWindowScalingFactorPropertyInfo = "window-scaling-factor"
    type AttrOrigin SettingsWindowScalingFactorPropertyInfo = Settings
    attrGet = getSettingsWindowScalingFactor
    attrSet = setSettingsWindowScalingFactor
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsWindowScalingFactor
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.Settings.windowScalingFactor"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-Settings.html#g:attr:windowScalingFactor"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Settings
type instance O.AttributeList Settings = SettingsAttributeList
type SettingsAttributeList = ('[ '("backend", SettingsBackendPropertyInfo), '("dndDragThreshold", SettingsDndDragThresholdPropertyInfo), '("doubleClickDistance", SettingsDoubleClickDistancePropertyInfo), '("doubleClickTime", SettingsDoubleClickTimePropertyInfo), '("fontAntialias", SettingsFontAntialiasPropertyInfo), '("fontDpi", SettingsFontDpiPropertyInfo), '("fontHintStyle", SettingsFontHintStylePropertyInfo), '("fontHinting", SettingsFontHintingPropertyInfo), '("fontName", SettingsFontNamePropertyInfo), '("fontSubpixelOrder", SettingsFontSubpixelOrderPropertyInfo), '("fontconfigTimestamp", SettingsFontconfigTimestampPropertyInfo), '("longPressDuration", SettingsLongPressDurationPropertyInfo), '("passwordHintTime", SettingsPasswordHintTimePropertyInfo), '("unscaledFontDpi", SettingsUnscaledFontDpiPropertyInfo), '("windowScalingFactor", SettingsWindowScalingFactorPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
settingsBackend :: AttrLabelProxy "backend"
settingsBackend = AttrLabelProxy

settingsDndDragThreshold :: AttrLabelProxy "dndDragThreshold"
settingsDndDragThreshold = AttrLabelProxy

settingsDoubleClickDistance :: AttrLabelProxy "doubleClickDistance"
settingsDoubleClickDistance = AttrLabelProxy

settingsDoubleClickTime :: AttrLabelProxy "doubleClickTime"
settingsDoubleClickTime = AttrLabelProxy

settingsFontAntialias :: AttrLabelProxy "fontAntialias"
settingsFontAntialias = AttrLabelProxy

settingsFontDpi :: AttrLabelProxy "fontDpi"
settingsFontDpi = AttrLabelProxy

settingsFontHintStyle :: AttrLabelProxy "fontHintStyle"
settingsFontHintStyle = AttrLabelProxy

settingsFontHinting :: AttrLabelProxy "fontHinting"
settingsFontHinting = AttrLabelProxy

settingsFontName :: AttrLabelProxy "fontName"
settingsFontName = AttrLabelProxy

settingsFontSubpixelOrder :: AttrLabelProxy "fontSubpixelOrder"
settingsFontSubpixelOrder = AttrLabelProxy

settingsFontconfigTimestamp :: AttrLabelProxy "fontconfigTimestamp"
settingsFontconfigTimestamp = AttrLabelProxy

settingsLongPressDuration :: AttrLabelProxy "longPressDuration"
settingsLongPressDuration = AttrLabelProxy

settingsPasswordHintTime :: AttrLabelProxy "passwordHintTime"
settingsPasswordHintTime = AttrLabelProxy

settingsUnscaledFontDpi :: AttrLabelProxy "unscaledFontDpi"
settingsUnscaledFontDpi = AttrLabelProxy

settingsWindowScalingFactor :: AttrLabelProxy "windowScalingFactor"
settingsWindowScalingFactor = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Settings = SettingsSignalList
type SettingsSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method Settings::get_default
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Clutter" , name = "Settings" })
-- throws : False
-- Skip return : False

foreign import ccall "clutter_settings_get_default" clutter_settings_get_default :: 
    IO (Ptr Settings)

-- | Retrieves the singleton instance of t'GI.Clutter.Objects.Settings.Settings'
-- 
-- /Since: 1.4/
settingsGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Settings
    -- ^ __Returns:__ the instance of t'GI.Clutter.Objects.Settings.Settings'. The
    --   returned object is owned by Clutter and it should not be unreferenced
    --   directly
settingsGetDefault :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Settings
settingsGetDefault  = IO Settings -> m Settings
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Settings -> m Settings) -> IO Settings -> m Settings
forall a b. (a -> b) -> a -> b
$ do
    Ptr Settings
result <- IO (Ptr Settings)
clutter_settings_get_default
    Text -> Ptr Settings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingsGetDefault" Ptr Settings
result
    Settings
result' <- ((ManagedPtr Settings -> Settings) -> Ptr Settings -> IO Settings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Settings -> Settings
Settings) Ptr Settings
result
    Settings -> IO Settings
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Settings
result'

#if defined(ENABLE_OVERLOADING)
#endif