{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GtkSettings provide a mechanism to share global settings between
-- applications.
-- 
-- On the X window system, this sharing is realized by an
-- <http://www.freedesktop.org/wiki/Specifications/xsettings-spec XSettings>
-- manager that is usually part of the desktop environment, along with
-- utilities that let the user change these settings. In the absence of
-- an Xsettings manager, GTK+ reads default values for settings from
-- @settings.ini@ files in
-- @\/etc\/gtk-3.0@, @$XDG_CONFIG_DIRS\/gtk-3.0@
-- and @$XDG_CONFIG_HOME\/gtk-3.0@.
-- These files must be valid key files (see t'GI.GLib.Structs.KeyFile.KeyFile'), and have
-- a section called Settings. Themes can also provide default values
-- for settings by installing a @settings.ini@ file
-- next to their @gtk.css@ file.
-- 
-- Applications can override system-wide settings by setting the property
-- of the GtkSettings object with @/g_object_set()/@. This should be restricted
-- to special cases though; GtkSettings are not meant as an application
-- configuration facility. When doing so, you need to be aware that settings
-- that are specific to individual widgets may not be available before the
-- widget type has been realized at least once. The following example
-- demonstrates a way to do this:
-- 
-- === /C code/
-- >
-- >  gtk_init (&argc, &argv);
-- >
-- >  // make sure the type is realized
-- >  g_type_class_unref (g_type_class_ref (GTK_TYPE_IMAGE_MENU_ITEM));
-- >
-- >  g_object_set (gtk_settings_get_default (), "gtk-enable-animations", FALSE, NULL);
-- 
-- 
-- There is one GtkSettings instance per screen. It can be obtained with
-- 'GI.Gtk.Objects.Settings.settingsGetForScreen', but in many cases, it is more convenient
-- to use 'GI.Gtk.Objects.Widget.widgetGetSettings'. 'GI.Gtk.Objects.Settings.settingsGetDefault' returns the
-- GtkSettings instance for the default screen.

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

module GI.Gtk.Objects.Settings
    ( 

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


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveSettingsMethod                   ,
#endif


-- ** getDefault #method:getDefault#

    settingsGetDefault                      ,


-- ** getForScreen #method:getForScreen#

    settingsGetForScreen                    ,


-- ** installProperty #method:installProperty#

    settingsInstallProperty                 ,


-- ** installPropertyParser #method:installPropertyParser#

    settingsInstallPropertyParser           ,


-- ** resetProperty #method:resetProperty#

#if defined(ENABLE_OVERLOADING)
    SettingsResetPropertyMethodInfo         ,
#endif
    settingsResetProperty                   ,


-- ** setDoubleProperty #method:setDoubleProperty#

#if defined(ENABLE_OVERLOADING)
    SettingsSetDoublePropertyMethodInfo     ,
#endif
    settingsSetDoubleProperty               ,


-- ** setLongProperty #method:setLongProperty#

#if defined(ENABLE_OVERLOADING)
    SettingsSetLongPropertyMethodInfo       ,
#endif
    settingsSetLongProperty                 ,


-- ** setPropertyValue #method:setPropertyValue#

#if defined(ENABLE_OVERLOADING)
    SettingsSetPropertyValueMethodInfo      ,
#endif
    settingsSetPropertyValue                ,


-- ** setStringProperty #method:setStringProperty#

#if defined(ENABLE_OVERLOADING)
    SettingsSetStringPropertyMethodInfo     ,
#endif
    settingsSetStringProperty               ,




 -- * Properties
-- ** colorHash #attr:colorHash#

#if defined(ENABLE_OVERLOADING)
    SettingsColorHashPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    settingsColorHash                       ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkAlternativeButtonOrderPropertyInfo,
#endif
    constructSettingsGtkAlternativeButtonOrder,
    getSettingsGtkAlternativeButtonOrder    ,
    setSettingsGtkAlternativeButtonOrder    ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkAlternativeButtonOrder       ,
#endif


-- ** gtkAlternativeSortArrows #attr:gtkAlternativeSortArrows#
-- | Controls the direction of the sort indicators in sorted list and tree
-- views. By default an arrow pointing down means the column is sorted
-- in ascending order. When set to 'P.True', this order will be inverted.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkAlternativeSortArrowsPropertyInfo,
#endif
    constructSettingsGtkAlternativeSortArrows,
    getSettingsGtkAlternativeSortArrows     ,
    setSettingsGtkAlternativeSortArrows     ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkAlternativeSortArrows        ,
#endif


-- ** gtkApplicationPreferDarkTheme #attr:gtkApplicationPreferDarkTheme#
-- | Whether the application prefers to use a dark theme. If a GTK+ theme
-- includes a dark variant, it will be used instead of the configured
-- theme.
-- 
-- Some applications benefit from minimizing the amount of light pollution that
-- interferes with the content. Good candidates for dark themes are photo and
-- video editors that make the actual content get all the attention and minimize
-- the distraction of the chrome.
-- 
-- Dark themes should not be used for documents, where large spaces are white\/light
-- and the dark chrome creates too much contrast (web browser, text editor...).
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkApplicationPreferDarkThemePropertyInfo,
#endif
    constructSettingsGtkApplicationPreferDarkTheme,
    getSettingsGtkApplicationPreferDarkTheme,
    setSettingsGtkApplicationPreferDarkTheme,
#if defined(ENABLE_OVERLOADING)
    settingsGtkApplicationPreferDarkTheme   ,
#endif


-- ** gtkAutoMnemonics #attr:gtkAutoMnemonics#
-- | Whether mnemonics should be automatically shown and hidden when the user
-- presses the mnemonic activator.
-- 
-- /Since: 2.20/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkAutoMnemonicsPropertyInfo    ,
#endif
    constructSettingsGtkAutoMnemonics       ,
    getSettingsGtkAutoMnemonics             ,
    setSettingsGtkAutoMnemonics             ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkAutoMnemonics                ,
#endif


-- ** gtkButtonImages #attr:gtkButtonImages#
-- | Whether images should be shown on buttons
-- 
-- /Since: 2.4/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkButtonImagesPropertyInfo     ,
#endif
    constructSettingsGtkButtonImages        ,
    getSettingsGtkButtonImages              ,
    setSettingsGtkButtonImages              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkButtonImages                 ,
#endif


-- ** gtkCanChangeAccels #attr:gtkCanChangeAccels#
-- | Whether menu accelerators can be changed by pressing a key over the menu item.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkCanChangeAccelsPropertyInfo  ,
#endif
    constructSettingsGtkCanChangeAccels     ,
    getSettingsGtkCanChangeAccels           ,
    setSettingsGtkCanChangeAccels           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkCanChangeAccels              ,
#endif


-- ** gtkColorPalette #attr:gtkColorPalette#
-- | Palette to use in the deprecated color selector.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkColorPalettePropertyInfo     ,
#endif
    clearSettingsGtkColorPalette            ,
    constructSettingsGtkColorPalette        ,
    getSettingsGtkColorPalette              ,
    setSettingsGtkColorPalette              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkColorPalette                 ,
#endif


-- ** gtkColorScheme #attr:gtkColorScheme#
-- | A palette of named colors for use in themes. The format of the string is
-- >
-- >name1: color1
-- >name2: color2
-- >...
-- 
-- Color names must be acceptable as identifiers in the
-- [gtkrc][gtk3-Resource-Files] syntax, and
-- color specifications must be in the format accepted by
-- 'GI.Gdk.Functions.colorParse'.
-- 
-- Note that due to the way the color tables from different sources are
-- merged, color specifications will be converted to hexadecimal form
-- when getting this property.
-- 
-- Starting with GTK+ 2.12, the entries can alternatively be separated
-- by \';\' instead of newlines:
-- >
-- >name1: color1; name2: color2; ...
-- 
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkColorSchemePropertyInfo      ,
#endif
    clearSettingsGtkColorScheme             ,
    constructSettingsGtkColorScheme         ,
    getSettingsGtkColorScheme               ,
    setSettingsGtkColorScheme               ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkColorScheme                  ,
#endif


-- ** gtkCursorBlink #attr:gtkCursorBlink#
-- | Whether the cursor should blink.
-- 
-- Also see the t'GI.Gtk.Objects.Settings.Settings':@/gtk-cursor-blink-timeout/@ setting,
-- which allows more flexible control over cursor blinking.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkCursorBlinkPropertyInfo      ,
#endif
    constructSettingsGtkCursorBlink         ,
    getSettingsGtkCursorBlink               ,
    setSettingsGtkCursorBlink               ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkCursorBlink                  ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkCursorBlinkTimePropertyInfo  ,
#endif
    constructSettingsGtkCursorBlinkTime     ,
    getSettingsGtkCursorBlinkTime           ,
    setSettingsGtkCursorBlinkTime           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkCursorBlinkTime              ,
#endif


-- ** gtkCursorBlinkTimeout #attr:gtkCursorBlinkTimeout#
-- | Time after which the cursor stops blinking, in seconds.
-- The timer is reset after each user interaction.
-- 
-- Setting this to zero has the same effect as setting
-- t'GI.Gtk.Objects.Settings.Settings':@/gtk-cursor-blink/@ to 'P.False'.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkCursorBlinkTimeoutPropertyInfo,
#endif
    constructSettingsGtkCursorBlinkTimeout  ,
    getSettingsGtkCursorBlinkTimeout        ,
    setSettingsGtkCursorBlinkTimeout        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkCursorBlinkTimeout           ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkCursorThemeNamePropertyInfo  ,
#endif
    clearSettingsGtkCursorThemeName         ,
    constructSettingsGtkCursorThemeName     ,
    getSettingsGtkCursorThemeName           ,
    setSettingsGtkCursorThemeName           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkCursorThemeName              ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkCursorThemeSizePropertyInfo  ,
#endif
    constructSettingsGtkCursorThemeSize     ,
    getSettingsGtkCursorThemeSize           ,
    setSettingsGtkCursorThemeSize           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkCursorThemeSize              ,
#endif


-- ** gtkDecorationLayout #attr:gtkDecorationLayout#
-- | This setting determines which buttons should be put in the
-- titlebar of client-side decorated windows, and whether they
-- should be placed at the left of right.
-- 
-- The format of the string is button names, separated by commas.
-- A colon separates the buttons that should appear on the left
-- from those on the right. Recognized button names are minimize,
-- maximize, close, icon (the window icon) and menu (a menu button
-- for the fallback app menu).
-- 
-- For example, \"menu:minimize,maximize,close\" specifies a menu
-- on the left, and minimize, maximize and close buttons on the right.
-- 
-- Note that buttons will only be shown when they are meaningful.
-- E.g. a menu button only appears when the desktop shell does not
-- show the app menu, and a close button only appears on a window
-- that can be closed.
-- 
-- Also note that the setting can be overridden with the
-- t'GI.Gtk.Objects.HeaderBar.HeaderBar':@/decoration-layout/@ property.
-- 
-- /Since: 3.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkDecorationLayoutPropertyInfo ,
#endif
    clearSettingsGtkDecorationLayout        ,
    constructSettingsGtkDecorationLayout    ,
    getSettingsGtkDecorationLayout          ,
    setSettingsGtkDecorationLayout          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkDecorationLayout             ,
#endif


-- ** gtkDialogsUseHeader #attr:gtkDialogsUseHeader#
-- | Whether builtin GTK+ dialogs such as the file chooser, the
-- color chooser or the font chooser will use a header bar at
-- the top to show action widgets, or an action area at the bottom.
-- 
-- This setting does not affect custom dialogs using GtkDialog
-- directly, or message dialogs.
-- 
-- /Since: 3.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkDialogsUseHeaderPropertyInfo ,
#endif
    constructSettingsGtkDialogsUseHeader    ,
    getSettingsGtkDialogsUseHeader          ,
    setSettingsGtkDialogsUseHeader          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkDialogsUseHeader             ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkDndDragThresholdPropertyInfo ,
#endif
    constructSettingsGtkDndDragThreshold    ,
    getSettingsGtkDndDragThreshold          ,
    setSettingsGtkDndDragThreshold          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkDndDragThreshold             ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkDoubleClickDistancePropertyInfo,
#endif
    constructSettingsGtkDoubleClickDistance ,
    getSettingsGtkDoubleClickDistance       ,
    setSettingsGtkDoubleClickDistance       ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkDoubleClickDistance          ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkDoubleClickTimePropertyInfo  ,
#endif
    constructSettingsGtkDoubleClickTime     ,
    getSettingsGtkDoubleClickTime           ,
    setSettingsGtkDoubleClickTime           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkDoubleClickTime              ,
#endif


-- ** gtkEnableAccels #attr:gtkEnableAccels#
-- | Whether menu items should have visible accelerators which can be
-- activated.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEnableAccelsPropertyInfo     ,
#endif
    constructSettingsGtkEnableAccels        ,
    getSettingsGtkEnableAccels              ,
    setSettingsGtkEnableAccels              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEnableAccels                 ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEnableAnimationsPropertyInfo ,
#endif
    constructSettingsGtkEnableAnimations    ,
    getSettingsGtkEnableAnimations          ,
    setSettingsGtkEnableAnimations          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEnableAnimations             ,
#endif


-- ** gtkEnableEventSounds #attr:gtkEnableEventSounds#
-- | Whether to play any event sounds at all.
-- 
-- See the <http://www.freedesktop.org/wiki/Specifications/sound-theme-spec Sound Theme Specifications>
-- for more information on event sounds and sound themes.
-- 
-- GTK+ itself does not support event sounds, you have to use a loadable
-- module like the one that comes with libcanberra.
-- 
-- /Since: 2.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEnableEventSoundsPropertyInfo,
#endif
    constructSettingsGtkEnableEventSounds   ,
    getSettingsGtkEnableEventSounds         ,
    setSettingsGtkEnableEventSounds         ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEnableEventSounds            ,
#endif


-- ** gtkEnableInputFeedbackSounds #attr:gtkEnableInputFeedbackSounds#
-- | Whether to play event sounds as feedback to user input.
-- 
-- See the <http://www.freedesktop.org/wiki/Specifications/sound-theme-spec Sound Theme Specifications>
-- for more information on event sounds and sound themes.
-- 
-- GTK+ itself does not support event sounds, you have to use a loadable
-- module like the one that comes with libcanberra.
-- 
-- /Since: 2.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEnableInputFeedbackSoundsPropertyInfo,
#endif
    constructSettingsGtkEnableInputFeedbackSounds,
    getSettingsGtkEnableInputFeedbackSounds ,
    setSettingsGtkEnableInputFeedbackSounds ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEnableInputFeedbackSounds    ,
#endif


-- ** gtkEnableMnemonics #attr:gtkEnableMnemonics#
-- | Whether labels and menu items should have visible mnemonics which
-- can be activated.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEnableMnemonicsPropertyInfo  ,
#endif
    constructSettingsGtkEnableMnemonics     ,
    getSettingsGtkEnableMnemonics           ,
    setSettingsGtkEnableMnemonics           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEnableMnemonics              ,
#endif


-- ** gtkEnablePrimaryPaste #attr:gtkEnablePrimaryPaste#
-- | Whether a middle click on a mouse should paste the
-- \'PRIMARY\' clipboard content at the cursor location.
-- 
-- /Since: 3.4/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEnablePrimaryPastePropertyInfo,
#endif
    constructSettingsGtkEnablePrimaryPaste  ,
    getSettingsGtkEnablePrimaryPaste        ,
    setSettingsGtkEnablePrimaryPaste        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEnablePrimaryPaste           ,
#endif


-- ** gtkEnableTooltips #attr:gtkEnableTooltips#
-- | Whether tooltips should be shown on widgets.
-- 
-- /Since: 2.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEnableTooltipsPropertyInfo   ,
#endif
    constructSettingsGtkEnableTooltips      ,
    getSettingsGtkEnableTooltips            ,
    setSettingsGtkEnableTooltips            ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEnableTooltips               ,
#endif


-- ** gtkEntryPasswordHintTimeout #attr:gtkEntryPasswordHintTimeout#
-- | How long to show the last input character in hidden
-- entries. This value is in milliseconds. 0 disables showing the
-- last char. 600 is a good value for enabling it.
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEntryPasswordHintTimeoutPropertyInfo,
#endif
    constructSettingsGtkEntryPasswordHintTimeout,
    getSettingsGtkEntryPasswordHintTimeout  ,
    setSettingsGtkEntryPasswordHintTimeout  ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEntryPasswordHintTimeout     ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEntrySelectOnFocusPropertyInfo,
#endif
    constructSettingsGtkEntrySelectOnFocus  ,
    getSettingsGtkEntrySelectOnFocus        ,
    setSettingsGtkEntrySelectOnFocus        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEntrySelectOnFocus           ,
#endif


-- ** gtkErrorBell #attr:gtkErrorBell#
-- | When 'P.True', keyboard navigation and other input-related errors
-- will cause a beep. Since the error bell is implemented using
-- 'GI.Gdk.Objects.Window.windowBeep', the windowing system may offer ways to
-- configure the error bell in many ways, such as flashing the
-- window or similar visual effects.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkErrorBellPropertyInfo        ,
#endif
    constructSettingsGtkErrorBell           ,
    getSettingsGtkErrorBell                 ,
    setSettingsGtkErrorBell                 ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkErrorBell                    ,
#endif


-- ** gtkFallbackIconTheme #attr:gtkFallbackIconTheme#
-- | Name of a icon theme to fall back to.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkFallbackIconThemePropertyInfo,
#endif
    clearSettingsGtkFallbackIconTheme       ,
    constructSettingsGtkFallbackIconTheme   ,
    getSettingsGtkFallbackIconTheme         ,
    setSettingsGtkFallbackIconTheme         ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkFallbackIconTheme            ,
#endif


-- ** gtkFileChooserBackend #attr:gtkFileChooserBackend#
-- | Name of the GtkFileChooser backend to use by default.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkFileChooserBackendPropertyInfo,
#endif
    clearSettingsGtkFileChooserBackend      ,
    constructSettingsGtkFileChooserBackend  ,
    getSettingsGtkFileChooserBackend        ,
    setSettingsGtkFileChooserBackend        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkFileChooserBackend           ,
#endif


-- ** gtkFontName #attr:gtkFontName#
-- | The default font to use. GTK+ uses the family name and size from this string.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkFontNamePropertyInfo         ,
#endif
    clearSettingsGtkFontName                ,
    constructSettingsGtkFontName            ,
    getSettingsGtkFontName                  ,
    setSettingsGtkFontName                  ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkFontName                     ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkFontconfigTimestampPropertyInfo,
#endif
    constructSettingsGtkFontconfigTimestamp ,
    getSettingsGtkFontconfigTimestamp       ,
    setSettingsGtkFontconfigTimestamp       ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkFontconfigTimestamp          ,
#endif


-- ** gtkIconSizes #attr:gtkIconSizes#
-- | A list of icon sizes. The list is separated by colons, and
-- item has the form:
-- 
-- @size-name@ = @width@ , @height@
-- 
-- E.g. \"gtk-menu=16,16:gtk-button=20,20:gtk-dialog=48,48\".
-- GTK+ itself use the following named icon sizes: gtk-menu,
-- gtk-button, gtk-small-toolbar, gtk-large-toolbar, gtk-dnd,
-- gtk-dialog. Applications can register their own named icon
-- sizes with 'GI.Gtk.Functions.iconSizeRegister'.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkIconSizesPropertyInfo        ,
#endif
    clearSettingsGtkIconSizes               ,
    constructSettingsGtkIconSizes           ,
    getSettingsGtkIconSizes                 ,
    setSettingsGtkIconSizes                 ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkIconSizes                    ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkIconThemeNamePropertyInfo    ,
#endif
    clearSettingsGtkIconThemeName           ,
    constructSettingsGtkIconThemeName       ,
    getSettingsGtkIconThemeName             ,
    setSettingsGtkIconThemeName             ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkIconThemeName                ,
#endif


-- ** gtkImModule #attr:gtkImModule#
-- | Which IM (input method) module should be used by default. This is the
-- input method that will be used if the user has not explicitly chosen
-- another input method from the IM context menu.
-- This also can be a colon-separated list of input methods, which GTK+
-- will try in turn until it finds one available on the system.
-- 
-- See t'GI.Gtk.Objects.IMContext.IMContext'.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkImModulePropertyInfo         ,
#endif
    clearSettingsGtkImModule                ,
    constructSettingsGtkImModule            ,
    getSettingsGtkImModule                  ,
    setSettingsGtkImModule                  ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkImModule                     ,
#endif


-- ** gtkImPreeditStyle #attr:gtkImPreeditStyle#
-- | How to draw the input method preedit string.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkImPreeditStylePropertyInfo   ,
#endif
    constructSettingsGtkImPreeditStyle      ,
    getSettingsGtkImPreeditStyle            ,
    setSettingsGtkImPreeditStyle            ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkImPreeditStyle               ,
#endif


-- ** gtkImStatusStyle #attr:gtkImStatusStyle#
-- | How to draw the input method statusbar.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkImStatusStylePropertyInfo    ,
#endif
    constructSettingsGtkImStatusStyle       ,
    getSettingsGtkImStatusStyle             ,
    setSettingsGtkImStatusStyle             ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkImStatusStyle                ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkKeyThemeNamePropertyInfo     ,
#endif
    clearSettingsGtkKeyThemeName            ,
    constructSettingsGtkKeyThemeName        ,
    getSettingsGtkKeyThemeName              ,
    setSettingsGtkKeyThemeName              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkKeyThemeName                 ,
#endif


-- ** gtkKeynavCursorOnly #attr:gtkKeynavCursorOnly#
-- | When 'P.True', keyboard navigation should be able to reach all widgets
-- by using the cursor keys only. Tab, Shift etc. keys can\'t be expected
-- to be present on the used input device.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkKeynavCursorOnlyPropertyInfo ,
#endif
    constructSettingsGtkKeynavCursorOnly    ,
    getSettingsGtkKeynavCursorOnly          ,
    setSettingsGtkKeynavCursorOnly          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkKeynavCursorOnly             ,
#endif


-- ** gtkKeynavUseCaret #attr:gtkKeynavUseCaret#
-- | Whether GTK+ should make sure that text can be navigated with
-- a caret, even if it is not editable. This is useful when using
-- a screen reader.
-- 
-- /Since: 3.20/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkKeynavUseCaretPropertyInfo   ,
#endif
    constructSettingsGtkKeynavUseCaret      ,
    getSettingsGtkKeynavUseCaret            ,
    setSettingsGtkKeynavUseCaret            ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkKeynavUseCaret               ,
#endif


-- ** gtkKeynavWrapAround #attr:gtkKeynavWrapAround#
-- | When 'P.True', some widgets will wrap around when doing keyboard
-- navigation, such as menus, menubars and notebooks.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkKeynavWrapAroundPropertyInfo ,
#endif
    constructSettingsGtkKeynavWrapAround    ,
    getSettingsGtkKeynavWrapAround          ,
    setSettingsGtkKeynavWrapAround          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkKeynavWrapAround             ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkLabelSelectOnFocusPropertyInfo,
#endif
    constructSettingsGtkLabelSelectOnFocus  ,
    getSettingsGtkLabelSelectOnFocus        ,
    setSettingsGtkLabelSelectOnFocus        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkLabelSelectOnFocus           ,
#endif


-- ** gtkLongPressTime #attr:gtkLongPressTime#
-- | The time for a button or touch press to be considered a \"long press\".
-- 
-- /Since: 3.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkLongPressTimePropertyInfo    ,
#endif
    constructSettingsGtkLongPressTime       ,
    getSettingsGtkLongPressTime             ,
    setSettingsGtkLongPressTime             ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkLongPressTime                ,
#endif


-- ** gtkMenuBarAccel #attr:gtkMenuBarAccel#
-- | Keybinding to activate the menu bar.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkMenuBarAccelPropertyInfo     ,
#endif
    clearSettingsGtkMenuBarAccel            ,
    constructSettingsGtkMenuBarAccel        ,
    getSettingsGtkMenuBarAccel              ,
    setSettingsGtkMenuBarAccel              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkMenuBarAccel                 ,
#endif


-- ** gtkMenuBarPopupDelay #attr:gtkMenuBarPopupDelay#
-- | Delay before the submenus of a menu bar appear.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkMenuBarPopupDelayPropertyInfo,
#endif
    constructSettingsGtkMenuBarPopupDelay   ,
    getSettingsGtkMenuBarPopupDelay         ,
    setSettingsGtkMenuBarPopupDelay         ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkMenuBarPopupDelay            ,
#endif


-- ** gtkMenuImages #attr:gtkMenuImages#
-- | Whether images should be shown in menu items

#if defined(ENABLE_OVERLOADING)
    SettingsGtkMenuImagesPropertyInfo       ,
#endif
    constructSettingsGtkMenuImages          ,
    getSettingsGtkMenuImages                ,
    setSettingsGtkMenuImages                ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkMenuImages                   ,
#endif


-- ** gtkMenuPopdownDelay #attr:gtkMenuPopdownDelay#
-- | The time before hiding a submenu when the pointer is moving towards the submenu.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkMenuPopdownDelayPropertyInfo ,
#endif
    constructSettingsGtkMenuPopdownDelay    ,
    getSettingsGtkMenuPopdownDelay          ,
    setSettingsGtkMenuPopdownDelay          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkMenuPopdownDelay             ,
#endif


-- ** gtkMenuPopupDelay #attr:gtkMenuPopupDelay#
-- | Minimum time the pointer must stay over a menu item before the submenu appear.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkMenuPopupDelayPropertyInfo   ,
#endif
    constructSettingsGtkMenuPopupDelay      ,
    getSettingsGtkMenuPopupDelay            ,
    setSettingsGtkMenuPopupDelay            ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkMenuPopupDelay               ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkModulesPropertyInfo          ,
#endif
    clearSettingsGtkModules                 ,
    constructSettingsGtkModules             ,
    getSettingsGtkModules                   ,
    setSettingsGtkModules                   ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkModules                      ,
#endif


-- ** gtkOverlayScrolling #attr:gtkOverlayScrolling#
-- | Whether scrolled windows may use overlayed scrolling indicators.
-- If this is set to 'P.False', scrolled windows will have permanent
-- scrollbars.
-- 
-- /Since: 3.24.9/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkOverlayScrollingPropertyInfo ,
#endif
    constructSettingsGtkOverlayScrolling    ,
    getSettingsGtkOverlayScrolling          ,
    setSettingsGtkOverlayScrolling          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkOverlayScrolling             ,
#endif


-- ** gtkPrimaryButtonWarpsSlider #attr:gtkPrimaryButtonWarpsSlider#
-- | If the value of this setting is 'P.True', clicking the primary button in a
-- t'GI.Gtk.Objects.Range.Range' trough will move the slider, and hence set the range’s value, to
-- the point that you clicked. If it is 'P.False', a primary click will cause the
-- slider\/value to move by the range’s page-size towards the point clicked.
-- 
-- Whichever action you choose for the primary button, the other action will
-- be available by holding Shift and primary-clicking, or (since GTK+ 3.22.25)
-- clicking the middle mouse button.
-- 
-- /Since: 3.6/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkPrimaryButtonWarpsSliderPropertyInfo,
#endif
    constructSettingsGtkPrimaryButtonWarpsSlider,
    getSettingsGtkPrimaryButtonWarpsSlider  ,
    setSettingsGtkPrimaryButtonWarpsSlider  ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkPrimaryButtonWarpsSlider     ,
#endif


-- ** gtkPrintBackends #attr:gtkPrintBackends#
-- | A comma-separated list of print backends to use in the print
-- dialog. Available print backends depend on the GTK+ installation,
-- and may include \"file\", \"cups\", \"lpr\" or \"papi\".
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkPrintBackendsPropertyInfo    ,
#endif
    clearSettingsGtkPrintBackends           ,
    constructSettingsGtkPrintBackends       ,
    getSettingsGtkPrintBackends             ,
    setSettingsGtkPrintBackends             ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkPrintBackends                ,
#endif


-- ** gtkPrintPreviewCommand #attr:gtkPrintPreviewCommand#
-- | A command to run for displaying the print preview. The command
-- should contain a @%f@ placeholder, which will get replaced by
-- the path to the pdf file. The command may also contain a @%s@
-- placeholder, which will get replaced by the path to a file
-- containing the print settings in the format produced by
-- 'GI.Gtk.Objects.PrintSettings.printSettingsToFile'.
-- 
-- The preview application is responsible for removing the pdf file
-- and the print settings file when it is done.
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkPrintPreviewCommandPropertyInfo,
#endif
    clearSettingsGtkPrintPreviewCommand     ,
    constructSettingsGtkPrintPreviewCommand ,
    getSettingsGtkPrintPreviewCommand       ,
    setSettingsGtkPrintPreviewCommand       ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkPrintPreviewCommand          ,
#endif


-- ** gtkRecentFilesEnabled #attr:gtkRecentFilesEnabled#
-- | Whether GTK+ should keep track of items inside the recently used
-- resources list. If set to 'P.False', the list will always be empty.
-- 
-- /Since: 3.8/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkRecentFilesEnabledPropertyInfo,
#endif
    constructSettingsGtkRecentFilesEnabled  ,
    getSettingsGtkRecentFilesEnabled        ,
    setSettingsGtkRecentFilesEnabled        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkRecentFilesEnabled           ,
#endif


-- ** gtkRecentFilesLimit #attr:gtkRecentFilesLimit#
-- | The number of recently used files that should be displayed by default by
-- t'GI.Gtk.Interfaces.RecentChooser.RecentChooser' implementations and by the t'GI.Gtk.Interfaces.FileChooser.FileChooser'. A value of
-- -1 means every recently used file stored.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkRecentFilesLimitPropertyInfo ,
#endif
    constructSettingsGtkRecentFilesLimit    ,
    getSettingsGtkRecentFilesLimit          ,
    setSettingsGtkRecentFilesLimit          ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkRecentFilesLimit             ,
#endif


-- ** gtkRecentFilesMaxAge #attr:gtkRecentFilesMaxAge#
-- | The maximum age, in days, of the items inside the recently used
-- resources list. Items older than this setting will be excised
-- from the list. If set to 0, the list will always be empty; if
-- set to -1, no item will be removed.
-- 
-- /Since: 2.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkRecentFilesMaxAgePropertyInfo,
#endif
    constructSettingsGtkRecentFilesMaxAge   ,
    getSettingsGtkRecentFilesMaxAge         ,
    setSettingsGtkRecentFilesMaxAge         ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkRecentFilesMaxAge            ,
#endif


-- ** gtkScrolledWindowPlacement #attr:gtkScrolledWindowPlacement#
-- | Where the contents of scrolled windows are located with respect to the
-- scrollbars, if not overridden by the scrolled window\'s own placement.
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkScrolledWindowPlacementPropertyInfo,
#endif
    constructSettingsGtkScrolledWindowPlacement,
    getSettingsGtkScrolledWindowPlacement   ,
    setSettingsGtkScrolledWindowPlacement   ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkScrolledWindowPlacement      ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkShellShowsAppMenuPropertyInfo,
#endif
    constructSettingsGtkShellShowsAppMenu   ,
    getSettingsGtkShellShowsAppMenu         ,
    setSettingsGtkShellShowsAppMenu         ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkShellShowsAppMenu            ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkShellShowsDesktopPropertyInfo,
#endif
    constructSettingsGtkShellShowsDesktop   ,
    getSettingsGtkShellShowsDesktop         ,
    setSettingsGtkShellShowsDesktop         ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkShellShowsDesktop            ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkShellShowsMenubarPropertyInfo,
#endif
    constructSettingsGtkShellShowsMenubar   ,
    getSettingsGtkShellShowsMenubar         ,
    setSettingsGtkShellShowsMenubar         ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkShellShowsMenubar            ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkShowInputMethodMenuPropertyInfo,
#endif
    constructSettingsGtkShowInputMethodMenu ,
    getSettingsGtkShowInputMethodMenu       ,
    setSettingsGtkShowInputMethodMenu       ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkShowInputMethodMenu          ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkShowUnicodeMenuPropertyInfo  ,
#endif
    constructSettingsGtkShowUnicodeMenu     ,
    getSettingsGtkShowUnicodeMenu           ,
    setSettingsGtkShowUnicodeMenu           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkShowUnicodeMenu              ,
#endif


-- ** gtkSoundThemeName #attr:gtkSoundThemeName#
-- | The XDG sound theme to use for event sounds.
-- 
-- See the <http://www.freedesktop.org/wiki/Specifications/sound-theme-spec Sound Theme Specifications>
-- for more information on event sounds and sound themes.
-- 
-- GTK+ itself does not support event sounds, you have to use a loadable
-- module like the one that comes with libcanberra.
-- 
-- /Since: 2.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkSoundThemeNamePropertyInfo   ,
#endif
    clearSettingsGtkSoundThemeName          ,
    constructSettingsGtkSoundThemeName      ,
    getSettingsGtkSoundThemeName            ,
    setSettingsGtkSoundThemeName            ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkSoundThemeName               ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkSplitCursorPropertyInfo      ,
#endif
    constructSettingsGtkSplitCursor         ,
    getSettingsGtkSplitCursor               ,
    setSettingsGtkSplitCursor               ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkSplitCursor                  ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkThemeNamePropertyInfo        ,
#endif
    clearSettingsGtkThemeName               ,
    constructSettingsGtkThemeName           ,
    getSettingsGtkThemeName                 ,
    setSettingsGtkThemeName                 ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkThemeName                    ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTimeoutExpandPropertyInfo    ,
#endif
    constructSettingsGtkTimeoutExpand       ,
    getSettingsGtkTimeoutExpand             ,
    setSettingsGtkTimeoutExpand             ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTimeoutExpand                ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTimeoutInitialPropertyInfo   ,
#endif
    constructSettingsGtkTimeoutInitial      ,
    getSettingsGtkTimeoutInitial            ,
    setSettingsGtkTimeoutInitial            ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTimeoutInitial               ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTimeoutRepeatPropertyInfo    ,
#endif
    constructSettingsGtkTimeoutRepeat       ,
    getSettingsGtkTimeoutRepeat             ,
    setSettingsGtkTimeoutRepeat             ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTimeoutRepeat                ,
#endif


-- ** gtkTitlebarDoubleClick #attr:gtkTitlebarDoubleClick#
-- | This setting determines the action to take when a double-click
-- occurs on the titlebar of client-side decorated windows.
-- 
-- Recognized actions are minimize, toggle-maximize, menu, lower
-- or none.
-- 
-- /Since: 3.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTitlebarDoubleClickPropertyInfo,
#endif
    clearSettingsGtkTitlebarDoubleClick     ,
    constructSettingsGtkTitlebarDoubleClick ,
    getSettingsGtkTitlebarDoubleClick       ,
    setSettingsGtkTitlebarDoubleClick       ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTitlebarDoubleClick          ,
#endif


-- ** gtkTitlebarMiddleClick #attr:gtkTitlebarMiddleClick#
-- | This setting determines the action to take when a middle-click
-- occurs on the titlebar of client-side decorated windows.
-- 
-- Recognized actions are minimize, toggle-maximize, menu, lower
-- or none.
-- 
-- /Since: 3.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTitlebarMiddleClickPropertyInfo,
#endif
    clearSettingsGtkTitlebarMiddleClick     ,
    constructSettingsGtkTitlebarMiddleClick ,
    getSettingsGtkTitlebarMiddleClick       ,
    setSettingsGtkTitlebarMiddleClick       ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTitlebarMiddleClick          ,
#endif


-- ** gtkTitlebarRightClick #attr:gtkTitlebarRightClick#
-- | This setting determines the action to take when a right-click
-- occurs on the titlebar of client-side decorated windows.
-- 
-- Recognized actions are minimize, toggle-maximize, menu, lower
-- or none.
-- 
-- /Since: 3.14/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTitlebarRightClickPropertyInfo,
#endif
    clearSettingsGtkTitlebarRightClick      ,
    constructSettingsGtkTitlebarRightClick  ,
    getSettingsGtkTitlebarRightClick        ,
    setSettingsGtkTitlebarRightClick        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTitlebarRightClick           ,
#endif


-- ** gtkToolbarIconSize #attr:gtkToolbarIconSize#
-- | The size of icons in default toolbars.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkToolbarIconSizePropertyInfo  ,
#endif
    constructSettingsGtkToolbarIconSize     ,
    getSettingsGtkToolbarIconSize           ,
    setSettingsGtkToolbarIconSize           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkToolbarIconSize              ,
#endif


-- ** gtkToolbarStyle #attr:gtkToolbarStyle#
-- | The size of icons in default toolbars.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkToolbarStylePropertyInfo     ,
#endif
    constructSettingsGtkToolbarStyle        ,
    getSettingsGtkToolbarStyle              ,
    setSettingsGtkToolbarStyle              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkToolbarStyle                 ,
#endif


-- ** gtkTooltipBrowseModeTimeout #attr:gtkTooltipBrowseModeTimeout#
-- | Amount of time, in milliseconds, after which the browse mode
-- will be disabled.
-- 
-- See t'GI.Gtk.Objects.Settings.Settings':@/gtk-tooltip-browse-timeout/@ for more information
-- about browse mode.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTooltipBrowseModeTimeoutPropertyInfo,
#endif
    constructSettingsGtkTooltipBrowseModeTimeout,
    getSettingsGtkTooltipBrowseModeTimeout  ,
    setSettingsGtkTooltipBrowseModeTimeout  ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTooltipBrowseModeTimeout     ,
#endif


-- ** gtkTooltipBrowseTimeout #attr:gtkTooltipBrowseTimeout#
-- | Controls the time after which tooltips will appear when
-- browse mode is enabled, in milliseconds.
-- 
-- Browse mode is enabled when the mouse pointer moves off an object
-- where a tooltip was currently being displayed. If the mouse pointer
-- hits another object before the browse mode timeout expires (see
-- t'GI.Gtk.Objects.Settings.Settings':@/gtk-tooltip-browse-mode-timeout/@), it will take the
-- amount of milliseconds specified by this setting to popup the tooltip
-- for the new object.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTooltipBrowseTimeoutPropertyInfo,
#endif
    constructSettingsGtkTooltipBrowseTimeout,
    getSettingsGtkTooltipBrowseTimeout      ,
    setSettingsGtkTooltipBrowseTimeout      ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTooltipBrowseTimeout         ,
#endif


-- ** gtkTooltipTimeout #attr:gtkTooltipTimeout#
-- | Time, in milliseconds, after which a tooltip could appear if the
-- cursor is hovering on top of a widget.
-- 
-- /Since: 2.12/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTooltipTimeoutPropertyInfo   ,
#endif
    constructSettingsGtkTooltipTimeout      ,
    getSettingsGtkTooltipTimeout            ,
    setSettingsGtkTooltipTimeout            ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTooltipTimeout               ,
#endif


-- ** gtkTouchscreenMode #attr:gtkTouchscreenMode#
-- | When 'P.True', there are no motion notify events delivered on this screen,
-- and widgets can\'t use the pointer hovering them for any essential
-- functionality.
-- 
-- /Since: 2.10/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTouchscreenModePropertyInfo  ,
#endif
    constructSettingsGtkTouchscreenMode     ,
    getSettingsGtkTouchscreenMode           ,
    setSettingsGtkTouchscreenMode           ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTouchscreenMode              ,
#endif


-- ** gtkVisibleFocus #attr:gtkVisibleFocus#
-- | Whether \'focus rectangles\' should be always visible, never visible,
-- or hidden until the user starts to use the keyboard.
-- 
-- /Since: 3.2/

#if defined(ENABLE_OVERLOADING)
    SettingsGtkVisibleFocusPropertyInfo     ,
#endif
    constructSettingsGtkVisibleFocus        ,
    getSettingsGtkVisibleFocus              ,
    setSettingsGtkVisibleFocus              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkVisibleFocus                 ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkXftAntialiasPropertyInfo     ,
#endif
    constructSettingsGtkXftAntialias        ,
    getSettingsGtkXftAntialias              ,
    setSettingsGtkXftAntialias              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkXftAntialias                 ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkXftDpiPropertyInfo           ,
#endif
    constructSettingsGtkXftDpi              ,
    getSettingsGtkXftDpi                    ,
    setSettingsGtkXftDpi                    ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkXftDpi                       ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkXftHintingPropertyInfo       ,
#endif
    constructSettingsGtkXftHinting          ,
    getSettingsGtkXftHinting                ,
    setSettingsGtkXftHinting                ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkXftHinting                   ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkXftHintstylePropertyInfo     ,
#endif
    clearSettingsGtkXftHintstyle            ,
    constructSettingsGtkXftHintstyle        ,
    getSettingsGtkXftHintstyle              ,
    setSettingsGtkXftHintstyle              ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkXftHintstyle                 ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkXftRgbaPropertyInfo          ,
#endif
    clearSettingsGtkXftRgba                 ,
    constructSettingsGtkXftRgba             ,
    getSettingsGtkXftRgba                   ,
    setSettingsGtkXftRgba                   ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkXftRgba                      ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Screen as Gdk.Screen
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Structs.SettingsValue as Gtk.SettingsValue

-- | Memory-managed wrapper type.
newtype Settings = Settings (ManagedPtr Settings)
    deriving (Settings -> Settings -> Bool
(Settings -> Settings -> Bool)
-> (Settings -> Settings -> Bool) -> Eq Settings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Settings -> Settings -> Bool
$c/= :: Settings -> Settings -> Bool
== :: Settings -> Settings -> Bool
$c== :: Settings -> Settings -> Bool
Eq)
foreign import ccall "gtk_settings_get_type"
    c_gtk_settings_get_type :: IO GType

instance GObject Settings where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_settings_get_type
    

-- | Convert 'Settings' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Settings where
    toGValue :: Settings -> IO GValue
toGValue o :: Settings
o = do
        GType
gtype <- IO GType
c_gtk_settings_get_type
        Settings -> (Ptr Settings -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Settings
o (GType
-> (GValue -> Ptr Settings -> IO ()) -> Ptr Settings -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Settings -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Settings
fromGValue gv :: GValue
gv = do
        Ptr Settings
ptr <- GValue -> IO (Ptr Settings)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Settings)
        (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
        
    

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

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

-- | Cast to `Settings`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toSettings :: (MonadIO m, IsSettings o) => o -> m Settings
toSettings :: o -> m Settings
toSettings = IO Settings -> m Settings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Settings -> Settings
Settings

-- | A convenience alias for `Nothing` :: `Maybe` `Settings`.
noSettings :: Maybe Settings
noSettings :: Maybe Settings
noSettings = Maybe Settings
forall a. Maybe a
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 "resetProperty" o = SettingsResetPropertyMethodInfo
    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 "getIconFactory" o = Gtk.StyleProvider.StyleProviderGetIconFactoryMethodInfo
    ResolveSettingsMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingsMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingsMethod "getStyle" o = Gtk.StyleProvider.StyleProviderGetStyleMethodInfo
    ResolveSettingsMethod "getStyleProperty" o = Gtk.StyleProvider.StyleProviderGetStylePropertyMethodInfo
    ResolveSettingsMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingsMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingsMethod "setDoubleProperty" o = SettingsSetDoublePropertyMethodInfo
    ResolveSettingsMethod "setLongProperty" o = SettingsSetLongPropertyMethodInfo
    ResolveSettingsMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingsMethod "setPropertyValue" o = SettingsSetPropertyValueMethodInfo
    ResolveSettingsMethod "setStringProperty" o = SettingsSetStringPropertyMethodInfo
    ResolveSettingsMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveSettingsMethod t Settings, O.MethodInfo 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

#endif

-- XXX Generation of property "color-hash" of object "Settings" failed: Not implemented: "Property SettingsColorHash has unsupported transfer type TransferContainer"
#if defined(ENABLE_OVERLOADING)
-- XXX Placeholder
data SettingsColorHashPropertyInfo
instance AttrInfo SettingsColorHashPropertyInfo where
    type AttrAllowedOps SettingsColorHashPropertyInfo = '[]
    type AttrSetTypeConstraint SettingsColorHashPropertyInfo = (~) ()
    type AttrTransferTypeConstraint SettingsColorHashPropertyInfo = (~) ()
    type AttrTransferType SettingsColorHashPropertyInfo = ()
    type AttrBaseTypeConstraint SettingsColorHashPropertyInfo = (~) ()
    type AttrGetType SettingsColorHashPropertyInfo = ()
    type AttrLabel SettingsColorHashPropertyInfo = ""
    type AttrOrigin SettingsColorHashPropertyInfo = Settings
    attrGet = undefined
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
#endif

-- VVV Prop "gtk-alternative-button-order"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-alternative-button-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 #gtkAlternativeButtonOrder
-- @
getSettingsGtkAlternativeButtonOrder :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkAlternativeButtonOrder :: o -> m Bool
getSettingsGtkAlternativeButtonOrder obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-alternative-button-order"

-- | Set the value of the “@gtk-alternative-button-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 [ #gtkAlternativeButtonOrder 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkAlternativeButtonOrder :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkAlternativeButtonOrder :: o -> Bool -> m ()
setSettingsGtkAlternativeButtonOrder obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-alternative-button-order" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-alternative-button-order@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkAlternativeButtonOrder :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkAlternativeButtonOrder :: Bool -> IO (GValueConstruct o)
constructSettingsGtkAlternativeButtonOrder val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-alternative-button-order" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkAlternativeButtonOrderPropertyInfo
instance AttrInfo SettingsGtkAlternativeButtonOrderPropertyInfo where
    type AttrAllowedOps SettingsGtkAlternativeButtonOrderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkAlternativeButtonOrderPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkAlternativeButtonOrderPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkAlternativeButtonOrderPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkAlternativeButtonOrderPropertyInfo = Bool
    type AttrGetType SettingsGtkAlternativeButtonOrderPropertyInfo = Bool
    type AttrLabel SettingsGtkAlternativeButtonOrderPropertyInfo = "gtk-alternative-button-order"
    type AttrOrigin SettingsGtkAlternativeButtonOrderPropertyInfo = Settings
    attrGet = getSettingsGtkAlternativeButtonOrder
    attrSet = setSettingsGtkAlternativeButtonOrder
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkAlternativeButtonOrder
    attrClear = undefined
#endif

-- VVV Prop "gtk-alternative-sort-arrows"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-alternative-sort-arrows@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkAlternativeSortArrows
-- @
getSettingsGtkAlternativeSortArrows :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkAlternativeSortArrows :: o -> m Bool
getSettingsGtkAlternativeSortArrows obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-alternative-sort-arrows"

-- | Set the value of the “@gtk-alternative-sort-arrows@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkAlternativeSortArrows 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkAlternativeSortArrows :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkAlternativeSortArrows :: o -> Bool -> m ()
setSettingsGtkAlternativeSortArrows obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-alternative-sort-arrows" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-alternative-sort-arrows@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkAlternativeSortArrows :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkAlternativeSortArrows :: Bool -> IO (GValueConstruct o)
constructSettingsGtkAlternativeSortArrows val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-alternative-sort-arrows" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkAlternativeSortArrowsPropertyInfo
instance AttrInfo SettingsGtkAlternativeSortArrowsPropertyInfo where
    type AttrAllowedOps SettingsGtkAlternativeSortArrowsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkAlternativeSortArrowsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkAlternativeSortArrowsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkAlternativeSortArrowsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkAlternativeSortArrowsPropertyInfo = Bool
    type AttrGetType SettingsGtkAlternativeSortArrowsPropertyInfo = Bool
    type AttrLabel SettingsGtkAlternativeSortArrowsPropertyInfo = "gtk-alternative-sort-arrows"
    type AttrOrigin SettingsGtkAlternativeSortArrowsPropertyInfo = Settings
    attrGet = getSettingsGtkAlternativeSortArrows
    attrSet = setSettingsGtkAlternativeSortArrows
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkAlternativeSortArrows
    attrClear = undefined
#endif

-- VVV Prop "gtk-application-prefer-dark-theme"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-application-prefer-dark-theme@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkApplicationPreferDarkTheme
-- @
getSettingsGtkApplicationPreferDarkTheme :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkApplicationPreferDarkTheme :: o -> m Bool
getSettingsGtkApplicationPreferDarkTheme obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-application-prefer-dark-theme"

-- | Set the value of the “@gtk-application-prefer-dark-theme@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkApplicationPreferDarkTheme 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkApplicationPreferDarkTheme :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkApplicationPreferDarkTheme :: o -> Bool -> m ()
setSettingsGtkApplicationPreferDarkTheme obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-application-prefer-dark-theme" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-application-prefer-dark-theme@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkApplicationPreferDarkTheme :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkApplicationPreferDarkTheme :: Bool -> IO (GValueConstruct o)
constructSettingsGtkApplicationPreferDarkTheme val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-application-prefer-dark-theme" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkApplicationPreferDarkThemePropertyInfo
instance AttrInfo SettingsGtkApplicationPreferDarkThemePropertyInfo where
    type AttrAllowedOps SettingsGtkApplicationPreferDarkThemePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkApplicationPreferDarkThemePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkApplicationPreferDarkThemePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkApplicationPreferDarkThemePropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkApplicationPreferDarkThemePropertyInfo = Bool
    type AttrGetType SettingsGtkApplicationPreferDarkThemePropertyInfo = Bool
    type AttrLabel SettingsGtkApplicationPreferDarkThemePropertyInfo = "gtk-application-prefer-dark-theme"
    type AttrOrigin SettingsGtkApplicationPreferDarkThemePropertyInfo = Settings
    attrGet = getSettingsGtkApplicationPreferDarkTheme
    attrSet = setSettingsGtkApplicationPreferDarkTheme
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkApplicationPreferDarkTheme
    attrClear = undefined
#endif

-- VVV Prop "gtk-auto-mnemonics"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-auto-mnemonics@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkAutoMnemonics :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkAutoMnemonics :: Bool -> IO (GValueConstruct o)
constructSettingsGtkAutoMnemonics val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-auto-mnemonics" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkAutoMnemonicsPropertyInfo
instance AttrInfo SettingsGtkAutoMnemonicsPropertyInfo where
    type AttrAllowedOps SettingsGtkAutoMnemonicsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkAutoMnemonicsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkAutoMnemonicsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkAutoMnemonicsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkAutoMnemonicsPropertyInfo = Bool
    type AttrGetType SettingsGtkAutoMnemonicsPropertyInfo = Bool
    type AttrLabel SettingsGtkAutoMnemonicsPropertyInfo = "gtk-auto-mnemonics"
    type AttrOrigin SettingsGtkAutoMnemonicsPropertyInfo = Settings
    attrGet = getSettingsGtkAutoMnemonics
    attrSet = setSettingsGtkAutoMnemonics
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkAutoMnemonics
    attrClear = undefined
#endif

-- VVV Prop "gtk-button-images"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-button-images@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkButtonImages :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkButtonImages :: Bool -> IO (GValueConstruct o)
constructSettingsGtkButtonImages val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-button-images" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkButtonImagesPropertyInfo
instance AttrInfo SettingsGtkButtonImagesPropertyInfo where
    type AttrAllowedOps SettingsGtkButtonImagesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkButtonImagesPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkButtonImagesPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkButtonImagesPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkButtonImagesPropertyInfo = Bool
    type AttrGetType SettingsGtkButtonImagesPropertyInfo = Bool
    type AttrLabel SettingsGtkButtonImagesPropertyInfo = "gtk-button-images"
    type AttrOrigin SettingsGtkButtonImagesPropertyInfo = Settings
    attrGet = getSettingsGtkButtonImages
    attrSet = setSettingsGtkButtonImages
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkButtonImages
    attrClear = undefined
#endif

-- VVV Prop "gtk-can-change-accels"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-can-change-accels@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkCanChangeAccels
-- @
getSettingsGtkCanChangeAccels :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkCanChangeAccels :: o -> m Bool
getSettingsGtkCanChangeAccels obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-can-change-accels"

-- | Set the value of the “@gtk-can-change-accels@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkCanChangeAccels 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkCanChangeAccels :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkCanChangeAccels :: o -> Bool -> m ()
setSettingsGtkCanChangeAccels obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-can-change-accels" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-can-change-accels@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkCanChangeAccels :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkCanChangeAccels :: Bool -> IO (GValueConstruct o)
constructSettingsGtkCanChangeAccels val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-can-change-accels" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkCanChangeAccelsPropertyInfo
instance AttrInfo SettingsGtkCanChangeAccelsPropertyInfo where
    type AttrAllowedOps SettingsGtkCanChangeAccelsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkCanChangeAccelsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkCanChangeAccelsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkCanChangeAccelsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkCanChangeAccelsPropertyInfo = Bool
    type AttrGetType SettingsGtkCanChangeAccelsPropertyInfo = Bool
    type AttrLabel SettingsGtkCanChangeAccelsPropertyInfo = "gtk-can-change-accels"
    type AttrOrigin SettingsGtkCanChangeAccelsPropertyInfo = Settings
    attrGet = getSettingsGtkCanChangeAccels
    attrSet = setSettingsGtkCanChangeAccels
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkCanChangeAccels
    attrClear = undefined
#endif

-- VVV Prop "gtk-color-palette"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@gtk-color-palette@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkColorPalette 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkColorPalette :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkColorPalette :: o -> Text -> m ()
setSettingsGtkColorPalette obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-color-palette" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-color-palette@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkColorPalette :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkColorPalette :: Text -> IO (GValueConstruct o)
constructSettingsGtkColorPalette val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-color-palette" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-color-palette@” 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' #gtkColorPalette
-- @
clearSettingsGtkColorPalette :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkColorPalette :: o -> m ()
clearSettingsGtkColorPalette obj :: o
obj = IO () -> m ()
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 "gtk-color-palette" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkColorPalettePropertyInfo
instance AttrInfo SettingsGtkColorPalettePropertyInfo where
    type AttrAllowedOps SettingsGtkColorPalettePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkColorPalettePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkColorPalettePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkColorPalettePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkColorPalettePropertyInfo = T.Text
    type AttrGetType SettingsGtkColorPalettePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkColorPalettePropertyInfo = "gtk-color-palette"
    type AttrOrigin SettingsGtkColorPalettePropertyInfo = Settings
    attrGet = getSettingsGtkColorPalette
    attrSet = setSettingsGtkColorPalette
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkColorPalette
    attrClear = clearSettingsGtkColorPalette
#endif

-- VVV Prop "gtk-color-scheme"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@gtk-color-scheme@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkColorScheme 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkColorScheme :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkColorScheme :: o -> Text -> m ()
setSettingsGtkColorScheme obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-color-scheme" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-color-scheme@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkColorScheme :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkColorScheme :: Text -> IO (GValueConstruct o)
constructSettingsGtkColorScheme val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-color-scheme" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-color-scheme@” 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' #gtkColorScheme
-- @
clearSettingsGtkColorScheme :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkColorScheme :: o -> m ()
clearSettingsGtkColorScheme obj :: o
obj = IO () -> m ()
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 "gtk-color-scheme" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkColorSchemePropertyInfo
instance AttrInfo SettingsGtkColorSchemePropertyInfo where
    type AttrAllowedOps SettingsGtkColorSchemePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkColorSchemePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkColorSchemePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkColorSchemePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkColorSchemePropertyInfo = T.Text
    type AttrGetType SettingsGtkColorSchemePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkColorSchemePropertyInfo = "gtk-color-scheme"
    type AttrOrigin SettingsGtkColorSchemePropertyInfo = Settings
    attrGet = getSettingsGtkColorScheme
    attrSet = setSettingsGtkColorScheme
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkColorScheme
    attrClear = clearSettingsGtkColorScheme
#endif

-- VVV Prop "gtk-cursor-blink"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-cursor-blink@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkCursorBlink :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkCursorBlink :: Bool -> IO (GValueConstruct o)
constructSettingsGtkCursorBlink val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-cursor-blink" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkCursorBlinkPropertyInfo
instance AttrInfo SettingsGtkCursorBlinkPropertyInfo where
    type AttrAllowedOps SettingsGtkCursorBlinkPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkCursorBlinkPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkCursorBlinkPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkCursorBlinkPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkCursorBlinkPropertyInfo = Bool
    type AttrGetType SettingsGtkCursorBlinkPropertyInfo = Bool
    type AttrLabel SettingsGtkCursorBlinkPropertyInfo = "gtk-cursor-blink"
    type AttrOrigin SettingsGtkCursorBlinkPropertyInfo = Settings
    attrGet = getSettingsGtkCursorBlink
    attrSet = setSettingsGtkCursorBlink
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkCursorBlink
    attrClear = undefined
#endif

-- VVV Prop "gtk-cursor-blink-time"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-cursor-blink-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 #gtkCursorBlinkTime
-- @
getSettingsGtkCursorBlinkTime :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsGtkCursorBlinkTime :: o -> m Int32
getSettingsGtkCursorBlinkTime obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "gtk-cursor-blink-time"

-- | Set the value of the “@gtk-cursor-blink-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 [ #gtkCursorBlinkTime 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkCursorBlinkTime :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsGtkCursorBlinkTime :: o -> Int32 -> m ()
setSettingsGtkCursorBlinkTime obj :: o
obj val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "gtk-cursor-blink-time" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-cursor-blink-time@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkCursorBlinkTime :: (IsSettings o) => Int32 -> IO (GValueConstruct o)
constructSettingsGtkCursorBlinkTime :: Int32 -> IO (GValueConstruct o)
constructSettingsGtkCursorBlinkTime val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "gtk-cursor-blink-time" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkCursorBlinkTimePropertyInfo
instance AttrInfo SettingsGtkCursorBlinkTimePropertyInfo where
    type AttrAllowedOps SettingsGtkCursorBlinkTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkCursorBlinkTimePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkCursorBlinkTimePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkCursorBlinkTimePropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkCursorBlinkTimePropertyInfo = Int32
    type AttrGetType SettingsGtkCursorBlinkTimePropertyInfo = Int32
    type AttrLabel SettingsGtkCursorBlinkTimePropertyInfo = "gtk-cursor-blink-time"
    type AttrOrigin SettingsGtkCursorBlinkTimePropertyInfo = Settings
    attrGet = getSettingsGtkCursorBlinkTime
    attrSet = setSettingsGtkCursorBlinkTime
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkCursorBlinkTime
    attrClear = undefined
#endif

-- VVV Prop "gtk-cursor-blink-timeout"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-cursor-blink-timeout@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkCursorBlinkTimeout :: (IsSettings o) => Int32 -> IO (GValueConstruct o)
constructSettingsGtkCursorBlinkTimeout :: Int32 -> IO (GValueConstruct o)
constructSettingsGtkCursorBlinkTimeout val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "gtk-cursor-blink-timeout" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkCursorBlinkTimeoutPropertyInfo
instance AttrInfo SettingsGtkCursorBlinkTimeoutPropertyInfo where
    type AttrAllowedOps SettingsGtkCursorBlinkTimeoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkCursorBlinkTimeoutPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkCursorBlinkTimeoutPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkCursorBlinkTimeoutPropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkCursorBlinkTimeoutPropertyInfo = Int32
    type AttrGetType SettingsGtkCursorBlinkTimeoutPropertyInfo = Int32
    type AttrLabel SettingsGtkCursorBlinkTimeoutPropertyInfo = "gtk-cursor-blink-timeout"
    type AttrOrigin SettingsGtkCursorBlinkTimeoutPropertyInfo = Settings
    attrGet = getSettingsGtkCursorBlinkTimeout
    attrSet = setSettingsGtkCursorBlinkTimeout
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkCursorBlinkTimeout
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-cursor-theme-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 #gtkCursorThemeName
-- @
getSettingsGtkCursorThemeName :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkCursorThemeName :: o -> m (Maybe Text)
getSettingsGtkCursorThemeName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "gtk-cursor-theme-name"

-- | Set the value of the “@gtk-cursor-theme-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 [ #gtkCursorThemeName 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkCursorThemeName :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkCursorThemeName :: o -> Text -> m ()
setSettingsGtkCursorThemeName obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-cursor-theme-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-cursor-theme-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkCursorThemeName :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkCursorThemeName :: Text -> IO (GValueConstruct o)
constructSettingsGtkCursorThemeName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-cursor-theme-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-cursor-theme-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' #gtkCursorThemeName
-- @
clearSettingsGtkCursorThemeName :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkCursorThemeName :: o -> m ()
clearSettingsGtkCursorThemeName obj :: o
obj = IO () -> m ()
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 "gtk-cursor-theme-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkCursorThemeNamePropertyInfo
instance AttrInfo SettingsGtkCursorThemeNamePropertyInfo where
    type AttrAllowedOps SettingsGtkCursorThemeNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkCursorThemeNamePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkCursorThemeNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkCursorThemeNamePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkCursorThemeNamePropertyInfo = T.Text
    type AttrGetType SettingsGtkCursorThemeNamePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkCursorThemeNamePropertyInfo = "gtk-cursor-theme-name"
    type AttrOrigin SettingsGtkCursorThemeNamePropertyInfo = Settings
    attrGet = getSettingsGtkCursorThemeName
    attrSet = setSettingsGtkCursorThemeName
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkCursorThemeName
    attrClear = clearSettingsGtkCursorThemeName
#endif

-- VVV Prop "gtk-cursor-theme-size"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-cursor-theme-size@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkCursorThemeSize :: (IsSettings o) => Int32 -> IO (GValueConstruct o)
constructSettingsGtkCursorThemeSize :: Int32 -> IO (GValueConstruct o)
constructSettingsGtkCursorThemeSize val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "gtk-cursor-theme-size" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkCursorThemeSizePropertyInfo
instance AttrInfo SettingsGtkCursorThemeSizePropertyInfo where
    type AttrAllowedOps SettingsGtkCursorThemeSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkCursorThemeSizePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkCursorThemeSizePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkCursorThemeSizePropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkCursorThemeSizePropertyInfo = Int32
    type AttrGetType SettingsGtkCursorThemeSizePropertyInfo = Int32
    type AttrLabel SettingsGtkCursorThemeSizePropertyInfo = "gtk-cursor-theme-size"
    type AttrOrigin SettingsGtkCursorThemeSizePropertyInfo = Settings
    attrGet = getSettingsGtkCursorThemeSize
    attrSet = setSettingsGtkCursorThemeSize
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkCursorThemeSize
    attrClear = undefined
#endif

-- VVV Prop "gtk-decoration-layout"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@gtk-decoration-layout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkDecorationLayout 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkDecorationLayout :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkDecorationLayout :: o -> Text -> m ()
setSettingsGtkDecorationLayout obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-decoration-layout" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-decoration-layout@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkDecorationLayout :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkDecorationLayout :: Text -> IO (GValueConstruct o)
constructSettingsGtkDecorationLayout val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-decoration-layout" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-decoration-layout@” 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' #gtkDecorationLayout
-- @
clearSettingsGtkDecorationLayout :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkDecorationLayout :: o -> m ()
clearSettingsGtkDecorationLayout obj :: o
obj = IO () -> m ()
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 "gtk-decoration-layout" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkDecorationLayoutPropertyInfo
instance AttrInfo SettingsGtkDecorationLayoutPropertyInfo where
    type AttrAllowedOps SettingsGtkDecorationLayoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkDecorationLayoutPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkDecorationLayoutPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkDecorationLayoutPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkDecorationLayoutPropertyInfo = T.Text
    type AttrGetType SettingsGtkDecorationLayoutPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkDecorationLayoutPropertyInfo = "gtk-decoration-layout"
    type AttrOrigin SettingsGtkDecorationLayoutPropertyInfo = Settings
    attrGet = getSettingsGtkDecorationLayout
    attrSet = setSettingsGtkDecorationLayout
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkDecorationLayout
    attrClear = clearSettingsGtkDecorationLayout
#endif

-- VVV Prop "gtk-dialogs-use-header"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-dialogs-use-header@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkDialogsUseHeader
-- @
getSettingsGtkDialogsUseHeader :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkDialogsUseHeader :: o -> m Bool
getSettingsGtkDialogsUseHeader obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-dialogs-use-header"

-- | Set the value of the “@gtk-dialogs-use-header@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkDialogsUseHeader 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkDialogsUseHeader :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkDialogsUseHeader :: o -> Bool -> m ()
setSettingsGtkDialogsUseHeader obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-dialogs-use-header" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-dialogs-use-header@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkDialogsUseHeader :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkDialogsUseHeader :: Bool -> IO (GValueConstruct o)
constructSettingsGtkDialogsUseHeader val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-dialogs-use-header" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkDialogsUseHeaderPropertyInfo
instance AttrInfo SettingsGtkDialogsUseHeaderPropertyInfo where
    type AttrAllowedOps SettingsGtkDialogsUseHeaderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkDialogsUseHeaderPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkDialogsUseHeaderPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkDialogsUseHeaderPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkDialogsUseHeaderPropertyInfo = Bool
    type AttrGetType SettingsGtkDialogsUseHeaderPropertyInfo = Bool
    type AttrLabel SettingsGtkDialogsUseHeaderPropertyInfo = "gtk-dialogs-use-header"
    type AttrOrigin SettingsGtkDialogsUseHeaderPropertyInfo = Settings
    attrGet = getSettingsGtkDialogsUseHeader
    attrSet = setSettingsGtkDialogsUseHeader
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkDialogsUseHeader
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-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 #gtkDndDragThreshold
-- @
getSettingsGtkDndDragThreshold :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsGtkDndDragThreshold :: o -> m Int32
getSettingsGtkDndDragThreshold obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "gtk-dnd-drag-threshold"

-- | Set the value of the “@gtk-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 [ #gtkDndDragThreshold 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkDndDragThreshold :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsGtkDndDragThreshold :: o -> Int32 -> m ()
setSettingsGtkDndDragThreshold obj :: o
obj val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "gtk-dnd-drag-threshold" Int32
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkDndDragThresholdPropertyInfo
instance AttrInfo SettingsGtkDndDragThresholdPropertyInfo where
    type AttrAllowedOps SettingsGtkDndDragThresholdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkDndDragThresholdPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkDndDragThresholdPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkDndDragThresholdPropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkDndDragThresholdPropertyInfo = Int32
    type AttrGetType SettingsGtkDndDragThresholdPropertyInfo = Int32
    type AttrLabel SettingsGtkDndDragThresholdPropertyInfo = "gtk-dnd-drag-threshold"
    type AttrOrigin SettingsGtkDndDragThresholdPropertyInfo = Settings
    attrGet = getSettingsGtkDndDragThreshold
    attrSet = setSettingsGtkDndDragThreshold
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkDndDragThreshold
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-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 #gtkDoubleClickDistance
-- @
getSettingsGtkDoubleClickDistance :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsGtkDoubleClickDistance :: o -> m Int32
getSettingsGtkDoubleClickDistance obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "gtk-double-click-distance"

-- | Set the value of the “@gtk-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 [ #gtkDoubleClickDistance 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkDoubleClickDistance :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsGtkDoubleClickDistance :: o -> Int32 -> m ()
setSettingsGtkDoubleClickDistance obj :: o
obj val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "gtk-double-click-distance" Int32
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkDoubleClickDistancePropertyInfo
instance AttrInfo SettingsGtkDoubleClickDistancePropertyInfo where
    type AttrAllowedOps SettingsGtkDoubleClickDistancePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkDoubleClickDistancePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkDoubleClickDistancePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkDoubleClickDistancePropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkDoubleClickDistancePropertyInfo = Int32
    type AttrGetType SettingsGtkDoubleClickDistancePropertyInfo = Int32
    type AttrLabel SettingsGtkDoubleClickDistancePropertyInfo = "gtk-double-click-distance"
    type AttrOrigin SettingsGtkDoubleClickDistancePropertyInfo = Settings
    attrGet = getSettingsGtkDoubleClickDistance
    attrSet = setSettingsGtkDoubleClickDistance
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkDoubleClickDistance
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-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 #gtkDoubleClickTime
-- @
getSettingsGtkDoubleClickTime :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsGtkDoubleClickTime :: o -> m Int32
getSettingsGtkDoubleClickTime obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "gtk-double-click-time"

-- | Set the value of the “@gtk-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 [ #gtkDoubleClickTime 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkDoubleClickTime :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsGtkDoubleClickTime :: o -> Int32 -> m ()
setSettingsGtkDoubleClickTime obj :: o
obj val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj "gtk-double-click-time" Int32
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkDoubleClickTimePropertyInfo
instance AttrInfo SettingsGtkDoubleClickTimePropertyInfo where
    type AttrAllowedOps SettingsGtkDoubleClickTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkDoubleClickTimePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkDoubleClickTimePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkDoubleClickTimePropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkDoubleClickTimePropertyInfo = Int32
    type AttrGetType SettingsGtkDoubleClickTimePropertyInfo = Int32
    type AttrLabel SettingsGtkDoubleClickTimePropertyInfo = "gtk-double-click-time"
    type AttrOrigin SettingsGtkDoubleClickTimePropertyInfo = Settings
    attrGet = getSettingsGtkDoubleClickTime
    attrSet = setSettingsGtkDoubleClickTime
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkDoubleClickTime
    attrClear = undefined
#endif

-- VVV Prop "gtk-enable-accels"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-enable-accels@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEnableAccels :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableAccels :: Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableAccels val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-enable-accels" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEnableAccelsPropertyInfo
instance AttrInfo SettingsGtkEnableAccelsPropertyInfo where
    type AttrAllowedOps SettingsGtkEnableAccelsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEnableAccelsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEnableAccelsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkEnableAccelsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkEnableAccelsPropertyInfo = Bool
    type AttrGetType SettingsGtkEnableAccelsPropertyInfo = Bool
    type AttrLabel SettingsGtkEnableAccelsPropertyInfo = "gtk-enable-accels"
    type AttrOrigin SettingsGtkEnableAccelsPropertyInfo = Settings
    attrGet = getSettingsGtkEnableAccels
    attrSet = setSettingsGtkEnableAccels
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEnableAccels
    attrClear = undefined
#endif

-- VVV Prop "gtk-enable-animations"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-enable-animations@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEnableAnimations :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableAnimations :: Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableAnimations val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-enable-animations" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEnableAnimationsPropertyInfo
instance AttrInfo SettingsGtkEnableAnimationsPropertyInfo where
    type AttrAllowedOps SettingsGtkEnableAnimationsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEnableAnimationsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEnableAnimationsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkEnableAnimationsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkEnableAnimationsPropertyInfo = Bool
    type AttrGetType SettingsGtkEnableAnimationsPropertyInfo = Bool
    type AttrLabel SettingsGtkEnableAnimationsPropertyInfo = "gtk-enable-animations"
    type AttrOrigin SettingsGtkEnableAnimationsPropertyInfo = Settings
    attrGet = getSettingsGtkEnableAnimations
    attrSet = setSettingsGtkEnableAnimations
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEnableAnimations
    attrClear = undefined
#endif

-- VVV Prop "gtk-enable-event-sounds"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-enable-event-sounds@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkEnableEventSounds
-- @
getSettingsGtkEnableEventSounds :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkEnableEventSounds :: o -> m Bool
getSettingsGtkEnableEventSounds obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-enable-event-sounds"

-- | Set the value of the “@gtk-enable-event-sounds@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkEnableEventSounds 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkEnableEventSounds :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkEnableEventSounds :: o -> Bool -> m ()
setSettingsGtkEnableEventSounds obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-enable-event-sounds" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-enable-event-sounds@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEnableEventSounds :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableEventSounds :: Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableEventSounds val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-enable-event-sounds" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEnableEventSoundsPropertyInfo
instance AttrInfo SettingsGtkEnableEventSoundsPropertyInfo where
    type AttrAllowedOps SettingsGtkEnableEventSoundsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEnableEventSoundsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEnableEventSoundsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkEnableEventSoundsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkEnableEventSoundsPropertyInfo = Bool
    type AttrGetType SettingsGtkEnableEventSoundsPropertyInfo = Bool
    type AttrLabel SettingsGtkEnableEventSoundsPropertyInfo = "gtk-enable-event-sounds"
    type AttrOrigin SettingsGtkEnableEventSoundsPropertyInfo = Settings
    attrGet = getSettingsGtkEnableEventSounds
    attrSet = setSettingsGtkEnableEventSounds
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEnableEventSounds
    attrClear = undefined
#endif

-- VVV Prop "gtk-enable-input-feedback-sounds"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-enable-input-feedback-sounds@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkEnableInputFeedbackSounds
-- @
getSettingsGtkEnableInputFeedbackSounds :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkEnableInputFeedbackSounds :: o -> m Bool
getSettingsGtkEnableInputFeedbackSounds obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-enable-input-feedback-sounds"

-- | Set the value of the “@gtk-enable-input-feedback-sounds@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkEnableInputFeedbackSounds 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkEnableInputFeedbackSounds :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkEnableInputFeedbackSounds :: o -> Bool -> m ()
setSettingsGtkEnableInputFeedbackSounds obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-enable-input-feedback-sounds" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-enable-input-feedback-sounds@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEnableInputFeedbackSounds :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableInputFeedbackSounds :: Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableInputFeedbackSounds val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-enable-input-feedback-sounds" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEnableInputFeedbackSoundsPropertyInfo
instance AttrInfo SettingsGtkEnableInputFeedbackSoundsPropertyInfo where
    type AttrAllowedOps SettingsGtkEnableInputFeedbackSoundsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEnableInputFeedbackSoundsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEnableInputFeedbackSoundsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkEnableInputFeedbackSoundsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkEnableInputFeedbackSoundsPropertyInfo = Bool
    type AttrGetType SettingsGtkEnableInputFeedbackSoundsPropertyInfo = Bool
    type AttrLabel SettingsGtkEnableInputFeedbackSoundsPropertyInfo = "gtk-enable-input-feedback-sounds"
    type AttrOrigin SettingsGtkEnableInputFeedbackSoundsPropertyInfo = Settings
    attrGet = getSettingsGtkEnableInputFeedbackSounds
    attrSet = setSettingsGtkEnableInputFeedbackSounds
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEnableInputFeedbackSounds
    attrClear = undefined
#endif

-- VVV Prop "gtk-enable-mnemonics"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-enable-mnemonics@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEnableMnemonics :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableMnemonics :: Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableMnemonics val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-enable-mnemonics" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEnableMnemonicsPropertyInfo
instance AttrInfo SettingsGtkEnableMnemonicsPropertyInfo where
    type AttrAllowedOps SettingsGtkEnableMnemonicsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEnableMnemonicsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEnableMnemonicsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkEnableMnemonicsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkEnableMnemonicsPropertyInfo = Bool
    type AttrGetType SettingsGtkEnableMnemonicsPropertyInfo = Bool
    type AttrLabel SettingsGtkEnableMnemonicsPropertyInfo = "gtk-enable-mnemonics"
    type AttrOrigin SettingsGtkEnableMnemonicsPropertyInfo = Settings
    attrGet = getSettingsGtkEnableMnemonics
    attrSet = setSettingsGtkEnableMnemonics
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEnableMnemonics
    attrClear = undefined
#endif

-- VVV Prop "gtk-enable-primary-paste"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-enable-primary-paste@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkEnablePrimaryPaste
-- @
getSettingsGtkEnablePrimaryPaste :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkEnablePrimaryPaste :: o -> m Bool
getSettingsGtkEnablePrimaryPaste obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-enable-primary-paste"

-- | Set the value of the “@gtk-enable-primary-paste@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkEnablePrimaryPaste 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkEnablePrimaryPaste :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkEnablePrimaryPaste :: o -> Bool -> m ()
setSettingsGtkEnablePrimaryPaste obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-enable-primary-paste" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-enable-primary-paste@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEnablePrimaryPaste :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkEnablePrimaryPaste :: Bool -> IO (GValueConstruct o)
constructSettingsGtkEnablePrimaryPaste val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-enable-primary-paste" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEnablePrimaryPastePropertyInfo
instance AttrInfo SettingsGtkEnablePrimaryPastePropertyInfo where
    type AttrAllowedOps SettingsGtkEnablePrimaryPastePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEnablePrimaryPastePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEnablePrimaryPastePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkEnablePrimaryPastePropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkEnablePrimaryPastePropertyInfo = Bool
    type AttrGetType SettingsGtkEnablePrimaryPastePropertyInfo = Bool
    type AttrLabel SettingsGtkEnablePrimaryPastePropertyInfo = "gtk-enable-primary-paste"
    type AttrOrigin SettingsGtkEnablePrimaryPastePropertyInfo = Settings
    attrGet = getSettingsGtkEnablePrimaryPaste
    attrSet = setSettingsGtkEnablePrimaryPaste
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEnablePrimaryPaste
    attrClear = undefined
#endif

-- VVV Prop "gtk-enable-tooltips"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-enable-tooltips@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEnableTooltips :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableTooltips :: Bool -> IO (GValueConstruct o)
constructSettingsGtkEnableTooltips val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-enable-tooltips" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEnableTooltipsPropertyInfo
instance AttrInfo SettingsGtkEnableTooltipsPropertyInfo where
    type AttrAllowedOps SettingsGtkEnableTooltipsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEnableTooltipsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEnableTooltipsPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkEnableTooltipsPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkEnableTooltipsPropertyInfo = Bool
    type AttrGetType SettingsGtkEnableTooltipsPropertyInfo = Bool
    type AttrLabel SettingsGtkEnableTooltipsPropertyInfo = "gtk-enable-tooltips"
    type AttrOrigin SettingsGtkEnableTooltipsPropertyInfo = Settings
    attrGet = getSettingsGtkEnableTooltips
    attrSet = setSettingsGtkEnableTooltips
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEnableTooltips
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-entry-password-hint-timeout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkEntryPasswordHintTimeout
-- @
getSettingsGtkEntryPasswordHintTimeout :: (MonadIO m, IsSettings o) => o -> m Word32
getSettingsGtkEntryPasswordHintTimeout :: o -> m Word32
getSettingsGtkEntryPasswordHintTimeout obj :: o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "gtk-entry-password-hint-timeout"

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-entry-password-hint-timeout@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEntryPasswordHintTimeout :: (IsSettings o) => Word32 -> IO (GValueConstruct o)
constructSettingsGtkEntryPasswordHintTimeout :: Word32 -> IO (GValueConstruct o)
constructSettingsGtkEntryPasswordHintTimeout val :: Word32
val = String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 "gtk-entry-password-hint-timeout" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEntryPasswordHintTimeoutPropertyInfo
instance AttrInfo SettingsGtkEntryPasswordHintTimeoutPropertyInfo where
    type AttrAllowedOps SettingsGtkEntryPasswordHintTimeoutPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEntryPasswordHintTimeoutPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEntryPasswordHintTimeoutPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingsGtkEntryPasswordHintTimeoutPropertyInfo = (~) Word32
    type AttrTransferType SettingsGtkEntryPasswordHintTimeoutPropertyInfo = Word32
    type AttrGetType SettingsGtkEntryPasswordHintTimeoutPropertyInfo = Word32
    type AttrLabel SettingsGtkEntryPasswordHintTimeoutPropertyInfo = "gtk-entry-password-hint-timeout"
    type AttrOrigin SettingsGtkEntryPasswordHintTimeoutPropertyInfo = Settings
    attrGet = getSettingsGtkEntryPasswordHintTimeout
    attrSet = setSettingsGtkEntryPasswordHintTimeout
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEntryPasswordHintTimeout
    attrClear = undefined
#endif

-- VVV Prop "gtk-entry-select-on-focus"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-entry-select-on-focus@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkEntrySelectOnFocus
-- @
getSettingsGtkEntrySelectOnFocus :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkEntrySelectOnFocus :: o -> m Bool
getSettingsGtkEntrySelectOnFocus obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-entry-select-on-focus"

-- | Set the value of the “@gtk-entry-select-on-focus@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkEntrySelectOnFocus 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkEntrySelectOnFocus :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkEntrySelectOnFocus :: o -> Bool -> m ()
setSettingsGtkEntrySelectOnFocus obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-entry-select-on-focus" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-entry-select-on-focus@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkEntrySelectOnFocus :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkEntrySelectOnFocus :: Bool -> IO (GValueConstruct o)
constructSettingsGtkEntrySelectOnFocus val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-entry-select-on-focus" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkEntrySelectOnFocusPropertyInfo
instance AttrInfo SettingsGtkEntrySelectOnFocusPropertyInfo where
    type AttrAllowedOps SettingsGtkEntrySelectOnFocusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkEntrySelectOnFocusPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkEntrySelectOnFocusPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkEntrySelectOnFocusPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkEntrySelectOnFocusPropertyInfo = Bool
    type AttrGetType SettingsGtkEntrySelectOnFocusPropertyInfo = Bool
    type AttrLabel SettingsGtkEntrySelectOnFocusPropertyInfo = "gtk-entry-select-on-focus"
    type AttrOrigin SettingsGtkEntrySelectOnFocusPropertyInfo = Settings
    attrGet = getSettingsGtkEntrySelectOnFocus
    attrSet = setSettingsGtkEntrySelectOnFocus
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkEntrySelectOnFocus
    attrClear = undefined
#endif

-- VVV Prop "gtk-error-bell"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-error-bell@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkErrorBell :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkErrorBell :: Bool -> IO (GValueConstruct o)
constructSettingsGtkErrorBell val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-error-bell" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkErrorBellPropertyInfo
instance AttrInfo SettingsGtkErrorBellPropertyInfo where
    type AttrAllowedOps SettingsGtkErrorBellPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkErrorBellPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkErrorBellPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkErrorBellPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkErrorBellPropertyInfo = Bool
    type AttrGetType SettingsGtkErrorBellPropertyInfo = Bool
    type AttrLabel SettingsGtkErrorBellPropertyInfo = "gtk-error-bell"
    type AttrOrigin SettingsGtkErrorBellPropertyInfo = Settings
    attrGet = getSettingsGtkErrorBell
    attrSet = setSettingsGtkErrorBell
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkErrorBell
    attrClear = undefined
#endif

-- VVV Prop "gtk-fallback-icon-theme"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@gtk-fallback-icon-theme@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkFallbackIconTheme 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkFallbackIconTheme :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkFallbackIconTheme :: o -> Text -> m ()
setSettingsGtkFallbackIconTheme obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-fallback-icon-theme" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-fallback-icon-theme@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkFallbackIconTheme :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkFallbackIconTheme :: Text -> IO (GValueConstruct o)
constructSettingsGtkFallbackIconTheme val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-fallback-icon-theme" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-fallback-icon-theme@” 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' #gtkFallbackIconTheme
-- @
clearSettingsGtkFallbackIconTheme :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkFallbackIconTheme :: o -> m ()
clearSettingsGtkFallbackIconTheme obj :: o
obj = IO () -> m ()
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 "gtk-fallback-icon-theme" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkFallbackIconThemePropertyInfo
instance AttrInfo SettingsGtkFallbackIconThemePropertyInfo where
    type AttrAllowedOps SettingsGtkFallbackIconThemePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkFallbackIconThemePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkFallbackIconThemePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkFallbackIconThemePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkFallbackIconThemePropertyInfo = T.Text
    type AttrGetType SettingsGtkFallbackIconThemePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkFallbackIconThemePropertyInfo = "gtk-fallback-icon-theme"
    type AttrOrigin SettingsGtkFallbackIconThemePropertyInfo = Settings
    attrGet = getSettingsGtkFallbackIconTheme
    attrSet = setSettingsGtkFallbackIconTheme
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkFallbackIconTheme
    attrClear = clearSettingsGtkFallbackIconTheme
#endif

-- VVV Prop "gtk-file-chooser-backend"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@gtk-file-chooser-backend@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkFileChooserBackend 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkFileChooserBackend :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkFileChooserBackend :: o -> Text -> m ()
setSettingsGtkFileChooserBackend obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-file-chooser-backend" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-file-chooser-backend@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkFileChooserBackend :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkFileChooserBackend :: Text -> IO (GValueConstruct o)
constructSettingsGtkFileChooserBackend val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-file-chooser-backend" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-file-chooser-backend@” 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' #gtkFileChooserBackend
-- @
clearSettingsGtkFileChooserBackend :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkFileChooserBackend :: o -> m ()
clearSettingsGtkFileChooserBackend obj :: o
obj = IO () -> m ()
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 "gtk-file-chooser-backend" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkFileChooserBackendPropertyInfo
instance AttrInfo SettingsGtkFileChooserBackendPropertyInfo where
    type AttrAllowedOps SettingsGtkFileChooserBackendPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkFileChooserBackendPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkFileChooserBackendPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkFileChooserBackendPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkFileChooserBackendPropertyInfo = T.Text
    type AttrGetType SettingsGtkFileChooserBackendPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkFileChooserBackendPropertyInfo = "gtk-file-chooser-backend"
    type AttrOrigin SettingsGtkFileChooserBackendPropertyInfo = Settings
    attrGet = getSettingsGtkFileChooserBackend
    attrSet = setSettingsGtkFileChooserBackend
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkFileChooserBackend
    attrClear = clearSettingsGtkFileChooserBackend
#endif

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

-- | Get the value of the “@gtk-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 #gtkFontName
-- @
getSettingsGtkFontName :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkFontName :: o -> m (Maybe Text)
getSettingsGtkFontName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "gtk-font-name"

-- | Set the value of the “@gtk-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 [ #gtkFontName 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkFontName :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkFontName :: o -> Text -> m ()
setSettingsGtkFontName obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-font-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

-- | Set the value of the “@gtk-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' #gtkFontName
-- @
clearSettingsGtkFontName :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkFontName :: o -> m ()
clearSettingsGtkFontName obj :: o
obj = IO () -> m ()
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 "gtk-font-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkFontNamePropertyInfo
instance AttrInfo SettingsGtkFontNamePropertyInfo where
    type AttrAllowedOps SettingsGtkFontNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkFontNamePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkFontNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkFontNamePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkFontNamePropertyInfo = T.Text
    type AttrGetType SettingsGtkFontNamePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkFontNamePropertyInfo = "gtk-font-name"
    type AttrOrigin SettingsGtkFontNamePropertyInfo = Settings
    attrGet = getSettingsGtkFontName
    attrSet = setSettingsGtkFontName
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkFontName
    attrClear = clearSettingsGtkFontName
#endif

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

-- | Get the value of the “@gtk-fontconfig-timestamp@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkFontconfigTimestamp
-- @
getSettingsGtkFontconfigTimestamp :: (MonadIO m, IsSettings o) => o -> m Word32
getSettingsGtkFontconfigTimestamp :: o -> m Word32
getSettingsGtkFontconfigTimestamp obj :: o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "gtk-fontconfig-timestamp"

-- | Set the value of the “@gtk-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 [ #gtkFontconfigTimestamp 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkFontconfigTimestamp :: (MonadIO m, IsSettings o) => o -> Word32 -> m ()
setSettingsGtkFontconfigTimestamp :: o -> Word32 -> m ()
setSettingsGtkFontconfigTimestamp obj :: o
obj val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj "gtk-fontconfig-timestamp" Word32
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkFontconfigTimestampPropertyInfo
instance AttrInfo SettingsGtkFontconfigTimestampPropertyInfo where
    type AttrAllowedOps SettingsGtkFontconfigTimestampPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkFontconfigTimestampPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkFontconfigTimestampPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingsGtkFontconfigTimestampPropertyInfo = (~) Word32
    type AttrTransferType SettingsGtkFontconfigTimestampPropertyInfo = Word32
    type AttrGetType SettingsGtkFontconfigTimestampPropertyInfo = Word32
    type AttrLabel SettingsGtkFontconfigTimestampPropertyInfo = "gtk-fontconfig-timestamp"
    type AttrOrigin SettingsGtkFontconfigTimestampPropertyInfo = Settings
    attrGet = getSettingsGtkFontconfigTimestamp
    attrSet = setSettingsGtkFontconfigTimestamp
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkFontconfigTimestamp
    attrClear = undefined
#endif

-- VVV Prop "gtk-icon-sizes"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@gtk-icon-sizes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkIconSizes 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkIconSizes :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkIconSizes :: o -> Text -> m ()
setSettingsGtkIconSizes obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-icon-sizes" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-icon-sizes@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkIconSizes :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkIconSizes :: Text -> IO (GValueConstruct o)
constructSettingsGtkIconSizes val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-icon-sizes" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-icon-sizes@” 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' #gtkIconSizes
-- @
clearSettingsGtkIconSizes :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkIconSizes :: o -> m ()
clearSettingsGtkIconSizes obj :: o
obj = IO () -> m ()
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 "gtk-icon-sizes" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkIconSizesPropertyInfo
instance AttrInfo SettingsGtkIconSizesPropertyInfo where
    type AttrAllowedOps SettingsGtkIconSizesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkIconSizesPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkIconSizesPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkIconSizesPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkIconSizesPropertyInfo = T.Text
    type AttrGetType SettingsGtkIconSizesPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkIconSizesPropertyInfo = "gtk-icon-sizes"
    type AttrOrigin SettingsGtkIconSizesPropertyInfo = Settings
    attrGet = getSettingsGtkIconSizes
    attrSet = setSettingsGtkIconSizes
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkIconSizes
    attrClear = clearSettingsGtkIconSizes
#endif

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

-- | Get the value of the “@gtk-icon-theme-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 #gtkIconThemeName
-- @
getSettingsGtkIconThemeName :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkIconThemeName :: o -> m (Maybe Text)
getSettingsGtkIconThemeName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "gtk-icon-theme-name"

-- | Set the value of the “@gtk-icon-theme-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 [ #gtkIconThemeName 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkIconThemeName :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkIconThemeName :: o -> Text -> m ()
setSettingsGtkIconThemeName obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-icon-theme-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-icon-theme-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkIconThemeName :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkIconThemeName :: Text -> IO (GValueConstruct o)
constructSettingsGtkIconThemeName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-icon-theme-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-icon-theme-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' #gtkIconThemeName
-- @
clearSettingsGtkIconThemeName :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkIconThemeName :: o -> m ()
clearSettingsGtkIconThemeName obj :: o
obj = IO () -> m ()
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 "gtk-icon-theme-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkIconThemeNamePropertyInfo
instance AttrInfo SettingsGtkIconThemeNamePropertyInfo where
    type AttrAllowedOps SettingsGtkIconThemeNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkIconThemeNamePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkIconThemeNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkIconThemeNamePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkIconThemeNamePropertyInfo = T.Text
    type AttrGetType SettingsGtkIconThemeNamePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkIconThemeNamePropertyInfo = "gtk-icon-theme-name"
    type AttrOrigin SettingsGtkIconThemeNamePropertyInfo = Settings
    attrGet = getSettingsGtkIconThemeName
    attrSet = setSettingsGtkIconThemeName
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkIconThemeName
    attrClear = clearSettingsGtkIconThemeName
#endif

-- VVV Prop "gtk-im-module"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@gtk-im-module@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkImModule 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkImModule :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkImModule :: o -> Text -> m ()
setSettingsGtkImModule obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-im-module" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-im-module@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkImModule :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkImModule :: Text -> IO (GValueConstruct o)
constructSettingsGtkImModule val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-im-module" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-im-module@” 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' #gtkImModule
-- @
clearSettingsGtkImModule :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkImModule :: o -> m ()
clearSettingsGtkImModule obj :: o
obj = IO () -> m ()
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 "gtk-im-module" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkImModulePropertyInfo
instance AttrInfo SettingsGtkImModulePropertyInfo where
    type AttrAllowedOps SettingsGtkImModulePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkImModulePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkImModulePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkImModulePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkImModulePropertyInfo = T.Text
    type AttrGetType SettingsGtkImModulePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkImModulePropertyInfo = "gtk-im-module"
    type AttrOrigin SettingsGtkImModulePropertyInfo = Settings
    attrGet = getSettingsGtkImModule
    attrSet = setSettingsGtkImModule
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkImModule
    attrClear = clearSettingsGtkImModule
#endif

-- VVV Prop "gtk-im-preedit-style"
   -- Type: TInterface (Name {namespace = "Gtk", name = "IMPreeditStyle"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-im-preedit-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 #gtkImPreeditStyle
-- @
getSettingsGtkImPreeditStyle :: (MonadIO m, IsSettings o) => o -> m Gtk.Enums.IMPreeditStyle
getSettingsGtkImPreeditStyle :: o -> m IMPreeditStyle
getSettingsGtkImPreeditStyle obj :: o
obj = IO IMPreeditStyle -> m IMPreeditStyle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IMPreeditStyle -> m IMPreeditStyle)
-> IO IMPreeditStyle -> m IMPreeditStyle
forall a b. (a -> b) -> a -> b
$ o -> String -> IO IMPreeditStyle
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "gtk-im-preedit-style"

-- | Set the value of the “@gtk-im-preedit-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 [ #gtkImPreeditStyle 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkImPreeditStyle :: (MonadIO m, IsSettings o) => o -> Gtk.Enums.IMPreeditStyle -> m ()
setSettingsGtkImPreeditStyle :: o -> IMPreeditStyle -> m ()
setSettingsGtkImPreeditStyle obj :: o
obj val :: IMPreeditStyle
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> IMPreeditStyle -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj "gtk-im-preedit-style" IMPreeditStyle
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-im-preedit-style@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkImPreeditStyle :: (IsSettings o) => Gtk.Enums.IMPreeditStyle -> IO (GValueConstruct o)
constructSettingsGtkImPreeditStyle :: IMPreeditStyle -> IO (GValueConstruct o)
constructSettingsGtkImPreeditStyle val :: IMPreeditStyle
val = String -> IMPreeditStyle -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "gtk-im-preedit-style" IMPreeditStyle
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkImPreeditStylePropertyInfo
instance AttrInfo SettingsGtkImPreeditStylePropertyInfo where
    type AttrAllowedOps SettingsGtkImPreeditStylePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkImPreeditStylePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkImPreeditStylePropertyInfo = (~) Gtk.Enums.IMPreeditStyle
    type AttrTransferTypeConstraint SettingsGtkImPreeditStylePropertyInfo = (~) Gtk.Enums.IMPreeditStyle
    type AttrTransferType SettingsGtkImPreeditStylePropertyInfo = Gtk.Enums.IMPreeditStyle
    type AttrGetType SettingsGtkImPreeditStylePropertyInfo = Gtk.Enums.IMPreeditStyle
    type AttrLabel SettingsGtkImPreeditStylePropertyInfo = "gtk-im-preedit-style"
    type AttrOrigin SettingsGtkImPreeditStylePropertyInfo = Settings
    attrGet = getSettingsGtkImPreeditStyle
    attrSet = setSettingsGtkImPreeditStyle
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkImPreeditStyle
    attrClear = undefined
#endif

-- VVV Prop "gtk-im-status-style"
   -- Type: TInterface (Name {namespace = "Gtk", name = "IMStatusStyle"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-im-status-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 #gtkImStatusStyle
-- @
getSettingsGtkImStatusStyle :: (MonadIO m, IsSettings o) => o -> m Gtk.Enums.IMStatusStyle
getSettingsGtkImStatusStyle :: o -> m IMStatusStyle
getSettingsGtkImStatusStyle obj :: o
obj = IO IMStatusStyle -> m IMStatusStyle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IMStatusStyle -> m IMStatusStyle)
-> IO IMStatusStyle -> m IMStatusStyle
forall a b. (a -> b) -> a -> b
$ o -> String -> IO IMStatusStyle
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "gtk-im-status-style"

-- | Set the value of the “@gtk-im-status-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 [ #gtkImStatusStyle 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkImStatusStyle :: (MonadIO m, IsSettings o) => o -> Gtk.Enums.IMStatusStyle -> m ()
setSettingsGtkImStatusStyle :: o -> IMStatusStyle -> m ()
setSettingsGtkImStatusStyle obj :: o
obj val :: IMStatusStyle
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> IMStatusStyle -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj "gtk-im-status-style" IMStatusStyle
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-im-status-style@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkImStatusStyle :: (IsSettings o) => Gtk.Enums.IMStatusStyle -> IO (GValueConstruct o)
constructSettingsGtkImStatusStyle :: IMStatusStyle -> IO (GValueConstruct o)
constructSettingsGtkImStatusStyle val :: IMStatusStyle
val = String -> IMStatusStyle -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "gtk-im-status-style" IMStatusStyle
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkImStatusStylePropertyInfo
instance AttrInfo SettingsGtkImStatusStylePropertyInfo where
    type AttrAllowedOps SettingsGtkImStatusStylePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkImStatusStylePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkImStatusStylePropertyInfo = (~) Gtk.Enums.IMStatusStyle
    type AttrTransferTypeConstraint SettingsGtkImStatusStylePropertyInfo = (~) Gtk.Enums.IMStatusStyle
    type AttrTransferType SettingsGtkImStatusStylePropertyInfo = Gtk.Enums.IMStatusStyle
    type AttrGetType SettingsGtkImStatusStylePropertyInfo = Gtk.Enums.IMStatusStyle
    type AttrLabel SettingsGtkImStatusStylePropertyInfo = "gtk-im-status-style"
    type AttrOrigin SettingsGtkImStatusStylePropertyInfo = Settings
    attrGet = getSettingsGtkImStatusStyle
    attrSet = setSettingsGtkImStatusStyle
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkImStatusStyle
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-key-theme-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 #gtkKeyThemeName
-- @
getSettingsGtkKeyThemeName :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkKeyThemeName :: o -> m (Maybe Text)
getSettingsGtkKeyThemeName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "gtk-key-theme-name"

-- | Set the value of the “@gtk-key-theme-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 [ #gtkKeyThemeName 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkKeyThemeName :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkKeyThemeName :: o -> Text -> m ()
setSettingsGtkKeyThemeName obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-key-theme-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-key-theme-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkKeyThemeName :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkKeyThemeName :: Text -> IO (GValueConstruct o)
constructSettingsGtkKeyThemeName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-key-theme-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-key-theme-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' #gtkKeyThemeName
-- @
clearSettingsGtkKeyThemeName :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkKeyThemeName :: o -> m ()
clearSettingsGtkKeyThemeName obj :: o
obj = IO () -> m ()
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 "gtk-key-theme-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkKeyThemeNamePropertyInfo
instance AttrInfo SettingsGtkKeyThemeNamePropertyInfo where
    type AttrAllowedOps SettingsGtkKeyThemeNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkKeyThemeNamePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkKeyThemeNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkKeyThemeNamePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkKeyThemeNamePropertyInfo = T.Text
    type AttrGetType SettingsGtkKeyThemeNamePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkKeyThemeNamePropertyInfo = "gtk-key-theme-name"
    type AttrOrigin SettingsGtkKeyThemeNamePropertyInfo = Settings
    attrGet = getSettingsGtkKeyThemeName
    attrSet = setSettingsGtkKeyThemeName
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkKeyThemeName
    attrClear = clearSettingsGtkKeyThemeName
#endif

-- VVV Prop "gtk-keynav-cursor-only"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-keynav-cursor-only@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkKeynavCursorOnly
-- @
getSettingsGtkKeynavCursorOnly :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkKeynavCursorOnly :: o -> m Bool
getSettingsGtkKeynavCursorOnly obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-keynav-cursor-only"

-- | Set the value of the “@gtk-keynav-cursor-only@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkKeynavCursorOnly 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkKeynavCursorOnly :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkKeynavCursorOnly :: o -> Bool -> m ()
setSettingsGtkKeynavCursorOnly obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-keynav-cursor-only" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-keynav-cursor-only@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkKeynavCursorOnly :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkKeynavCursorOnly :: Bool -> IO (GValueConstruct o)
constructSettingsGtkKeynavCursorOnly val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-keynav-cursor-only" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkKeynavCursorOnlyPropertyInfo
instance AttrInfo SettingsGtkKeynavCursorOnlyPropertyInfo where
    type AttrAllowedOps SettingsGtkKeynavCursorOnlyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkKeynavCursorOnlyPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkKeynavCursorOnlyPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkKeynavCursorOnlyPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkKeynavCursorOnlyPropertyInfo = Bool
    type AttrGetType SettingsGtkKeynavCursorOnlyPropertyInfo = Bool
    type AttrLabel SettingsGtkKeynavCursorOnlyPropertyInfo = "gtk-keynav-cursor-only"
    type AttrOrigin SettingsGtkKeynavCursorOnlyPropertyInfo = Settings
    attrGet = getSettingsGtkKeynavCursorOnly
    attrSet = setSettingsGtkKeynavCursorOnly
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkKeynavCursorOnly
    attrClear = undefined
#endif

-- VVV Prop "gtk-keynav-use-caret"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-keynav-use-caret@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkKeynavUseCaret
-- @
getSettingsGtkKeynavUseCaret :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkKeynavUseCaret :: o -> m Bool
getSettingsGtkKeynavUseCaret obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-keynav-use-caret"

-- | Set the value of the “@gtk-keynav-use-caret@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkKeynavUseCaret 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkKeynavUseCaret :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkKeynavUseCaret :: o -> Bool -> m ()
setSettingsGtkKeynavUseCaret obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-keynav-use-caret" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-keynav-use-caret@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkKeynavUseCaret :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkKeynavUseCaret :: Bool -> IO (GValueConstruct o)
constructSettingsGtkKeynavUseCaret val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-keynav-use-caret" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkKeynavUseCaretPropertyInfo
instance AttrInfo SettingsGtkKeynavUseCaretPropertyInfo where
    type AttrAllowedOps SettingsGtkKeynavUseCaretPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkKeynavUseCaretPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkKeynavUseCaretPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkKeynavUseCaretPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkKeynavUseCaretPropertyInfo = Bool
    type AttrGetType SettingsGtkKeynavUseCaretPropertyInfo = Bool
    type AttrLabel SettingsGtkKeynavUseCaretPropertyInfo = "gtk-keynav-use-caret"
    type AttrOrigin SettingsGtkKeynavUseCaretPropertyInfo = Settings
    attrGet = getSettingsGtkKeynavUseCaret
    attrSet = setSettingsGtkKeynavUseCaret
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkKeynavUseCaret
    attrClear = undefined
#endif

-- VVV Prop "gtk-keynav-wrap-around"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-keynav-wrap-around@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkKeynavWrapAround
-- @
getSettingsGtkKeynavWrapAround :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkKeynavWrapAround :: o -> m Bool
getSettingsGtkKeynavWrapAround obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-keynav-wrap-around"

-- | Set the value of the “@gtk-keynav-wrap-around@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkKeynavWrapAround 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkKeynavWrapAround :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkKeynavWrapAround :: o -> Bool -> m ()
setSettingsGtkKeynavWrapAround obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-keynav-wrap-around" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-keynav-wrap-around@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkKeynavWrapAround :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkKeynavWrapAround :: Bool -> IO (GValueConstruct o)
constructSettingsGtkKeynavWrapAround val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-keynav-wrap-around" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkKeynavWrapAroundPropertyInfo
instance AttrInfo SettingsGtkKeynavWrapAroundPropertyInfo where
    type AttrAllowedOps SettingsGtkKeynavWrapAroundPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkKeynavWrapAroundPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkKeynavWrapAroundPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkKeynavWrapAroundPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkKeynavWrapAroundPropertyInfo = Bool
    type AttrGetType SettingsGtkKeynavWrapAroundPropertyInfo = Bool
    type AttrLabel SettingsGtkKeynavWrapAroundPropertyInfo = "gtk-keynav-wrap-around"
    type AttrOrigin SettingsGtkKeynavWrapAroundPropertyInfo = Settings
    attrGet = getSettingsGtkKeynavWrapAround
    attrSet = setSettingsGtkKeynavWrapAround
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkKeynavWrapAround
    attrClear = undefined
#endif

-- VVV Prop "gtk-label-select-on-focus"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-label-select-on-focus@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkLabelSelectOnFocus
-- @
getSettingsGtkLabelSelectOnFocus :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkLabelSelectOnFocus :: o -> m Bool
getSettingsGtkLabelSelectOnFocus obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "gtk-label-select-on-focus"

-- | Set the value of the “@gtk-label-select-on-focus@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkLabelSelectOnFocus 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkLabelSelectOnFocus :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkLabelSelectOnFocus :: o -> Bool -> m ()
setSettingsGtkLabelSelectOnFocus obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "gtk-label-select-on-focus" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-label-select-on-focus@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkLabelSelectOnFocus :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkLabelSelectOnFocus :: Bool -> IO (GValueConstruct o)
constructSettingsGtkLabelSelectOnFocus val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-label-select-on-focus" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkLabelSelectOnFocusPropertyInfo
instance AttrInfo SettingsGtkLabelSelectOnFocusPropertyInfo where
    type AttrAllowedOps SettingsGtkLabelSelectOnFocusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkLabelSelectOnFocusPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkLabelSelectOnFocusPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkLabelSelectOnFocusPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkLabelSelectOnFocusPropertyInfo = Bool
    type AttrGetType SettingsGtkLabelSelectOnFocusPropertyInfo = Bool
    type AttrLabel SettingsGtkLabelSelectOnFocusPropertyInfo = "gtk-label-select-on-focus"
    type AttrOrigin SettingsGtkLabelSelectOnFocusPropertyInfo = Settings
    attrGet = getSettingsGtkLabelSelectOnFocus
    attrSet = setSettingsGtkLabelSelectOnFocus
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkLabelSelectOnFocus
    attrClear = undefined
#endif

-- VVV Prop "gtk-long-press-time"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-long-press-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 #gtkLongPressTime
-- @
getSettingsGtkLongPressTime :: (MonadIO m, IsSettings o) => o -> m Word32
getSettingsGtkLongPressTime :: o -> m Word32
getSettingsGtkLongPressTime obj :: o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "gtk-long-press-time"

-- | Set the value of the “@gtk-long-press-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 [ #gtkLongPressTime 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkLongPressTime :: (MonadIO m, IsSettings o) => o -> Word32 -> m ()
setSettingsGtkLongPressTime :: o -> Word32 -> m ()
setSettingsGtkLongPressTime obj :: o
obj val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj "gtk-long-press-time" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@gtk-long-press-time@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkLongPressTime :: (IsSettings o) => Word32 -> IO (GValueConstruct o)
constructSettingsGtkLongPressTime :: Word32 -> IO (GValueConstruct o)
constructSettingsGtkLongPressTime val :: Word32
val = String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 "gtk-long-press-time" Word32
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkLongPressTimePropertyInfo
instance AttrInfo SettingsGtkLongPressTimePropertyInfo where
    type AttrAllowedOps SettingsGtkLongPressTimePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkLongPressTimePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkLongPressTimePropertyInfo = (~) Word32
    type AttrTransferTypeConstraint SettingsGtkLongPressTimePropertyInfo = (~) Word32
    type AttrTransferType SettingsGtkLongPressTimePropertyInfo = Word32
    type AttrGetType SettingsGtkLongPressTimePropertyInfo = Word32
    type AttrLabel SettingsGtkLongPressTimePropertyInfo = "gtk-long-press-time"
    type AttrOrigin SettingsGtkLongPressTimePropertyInfo = Settings
    attrGet = getSettingsGtkLongPressTime
    attrSet = setSettingsGtkLongPressTime
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkLongPressTime
    attrClear = undefined
#endif

-- VVV Prop "gtk-menu-bar-accel"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@gtk-menu-bar-accel@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkMenuBarAccel 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkMenuBarAccel :: (MonadIO m, IsSettings o) => o -> T.Text -> m ()
setSettingsGtkMenuBarAccel :: o -> Text -> m ()
setSettingsGtkMenuBarAccel obj :: o
obj val :: Text
val = IO () -> m ()
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 "gtk-menu-bar-accel" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@gtk-menu-bar-accel@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkMenuBarAccel :: (IsSettings o) => T.Text -> IO (GValueConstruct o)
constructSettingsGtkMenuBarAccel :: Text -> IO (GValueConstruct o)
constructSettingsGtkMenuBarAccel val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "gtk-menu-bar-accel" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@gtk-menu-bar-accel@” 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' #gtkMenuBarAccel
-- @
clearSettingsGtkMenuBarAccel :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkMenuBarAccel :: o -> m ()
clearSettingsGtkMenuBarAccel obj :: o
obj = IO () -> m ()
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 "gtk-menu-bar-accel" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkMenuBarAccelPropertyInfo
instance AttrInfo SettingsGtkMenuBarAccelPropertyInfo where
    type AttrAllowedOps SettingsGtkMenuBarAccelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkMenuBarAccelPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkMenuBarAccelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkMenuBarAccelPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkMenuBarAccelPropertyInfo = T.Text
    type AttrGetType SettingsGtkMenuBarAccelPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkMenuBarAccelPropertyInfo = "gtk-menu-bar-accel"
    type AttrOrigin SettingsGtkMenuBarAccelPropertyInfo = Settings
    attrGet = getSettingsGtkMenuBarAccel
    attrSet = setSettingsGtkMenuBarAccel
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkMenuBarAccel
    attrClear = clearSettingsGtkMenuBarAccel
#endif

-- VVV Prop "gtk-menu-bar-popup-delay"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-menu-bar-popup-delay@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkMenuBarPopupDelay :: (IsSettings o) => Int32 -> IO (GValueConstruct o)
constructSettingsGtkMenuBarPopupDelay :: Int32 -> IO (GValueConstruct o)
constructSettingsGtkMenuBarPopupDelay val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "gtk-menu-bar-popup-delay" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkMenuBarPopupDelayPropertyInfo
instance AttrInfo SettingsGtkMenuBarPopupDelayPropertyInfo where
    type AttrAllowedOps SettingsGtkMenuBarPopupDelayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkMenuBarPopupDelayPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkMenuBarPopupDelayPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkMenuBarPopupDelayPropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkMenuBarPopupDelayPropertyInfo = Int32
    type AttrGetType SettingsGtkMenuBarPopupDelayPropertyInfo = Int32
    type AttrLabel SettingsGtkMenuBarPopupDelayPropertyInfo = "gtk-menu-bar-popup-delay"
    type AttrOrigin SettingsGtkMenuBarPopupDelayPropertyInfo = Settings
    attrGet = getSettingsGtkMenuBarPopupDelay
    attrSet = setSettingsGtkMenuBarPopupDelay
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkMenuBarPopupDelay
    attrClear = undefined
#endif

-- VVV Prop "gtk-menu-images"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-menu-images@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkMenuImages :: (IsSettings o) => Bool -> IO (GValueConstruct o)
constructSettingsGtkMenuImages :: Bool -> IO (GValueConstruct o)
constructSettingsGtkMenuImages val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "gtk-menu-images" Bool
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkMenuImagesPropertyInfo
instance AttrInfo SettingsGtkMenuImagesPropertyInfo where
    type AttrAllowedOps SettingsGtkMenuImagesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkMenuImagesPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkMenuImagesPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkMenuImagesPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkMenuImagesPropertyInfo = Bool
    type AttrGetType SettingsGtkMenuImagesPropertyInfo = Bool
    type AttrLabel SettingsGtkMenuImagesPropertyInfo = "gtk-menu-images"
    type AttrOrigin SettingsGtkMenuImagesPropertyInfo = Settings
    attrGet = getSettingsGtkMenuImages
    attrSet = setSettingsGtkMenuImages
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkMenuImages
    attrClear = undefined
#endif

-- VVV Prop "gtk-menu-popdown-delay"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@gtk-menu-popdown-delay@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSettingsGtkMenuPopdownDelay :: (IsSettings o) => Int32 -> IO (GValueConstruct o)
constructSettingsGtkMenuPopdownDelay :: Int32 -> IO (GValueConstruct o)
constructSettingsGtkMenuPopdownDelay val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "gtk-menu-popdown-delay" Int32
val

#if defined(ENABLE_OVERLOADING)
data SettingsGtkMenuPopdownDelayPropertyInfo
instance AttrInfo SettingsGtkMenuPopdownDelayPropertyInfo where
</