{-# 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-4.0@, @$XDG_CONFIG_DIRS\/gtk-4.0@
-- and @$XDG_CONFIG_HOME\/gtk-4.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 ();
-- >
-- >  // make sure the type is realized
-- >  g_type_class_unref (g_type_class_ref (GTK_TYPE_BUTTON));
-- >
-- >  g_object_set (gtk_settings_get_default (), "gtk-enable-animations", FALSE, NULL);
-- 
-- 
-- There is one GtkSettings instance per display. It can be obtained with
-- 'GI.Gtk.Objects.Settings.settingsGetForDisplay', 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 display.

#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                      ,


-- ** getForDisplay #method:getForDisplay#

    settingsGetForDisplay                   ,


-- ** resetProperty #method:resetProperty#

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




 -- * Properties
-- ** 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.

#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...).

#if defined(ENABLE_OVERLOADING)
    SettingsGtkApplicationPreferDarkThemePropertyInfo,
#endif
    constructSettingsGtkApplicationPreferDarkTheme,
    getSettingsGtkApplicationPreferDarkTheme,
    setSettingsGtkApplicationPreferDarkTheme,
#if defined(ENABLE_OVERLOADING)
    settingsGtkApplicationPreferDarkTheme   ,
#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'.

#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.

#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.

#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.

#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.

#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.

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


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

#if defined(ENABLE_OVERLOADING)
    SettingsGtkEnablePrimaryPastePropertyInfo,
#endif
    constructSettingsGtkEnablePrimaryPaste  ,
    getSettingsGtkEnablePrimaryPaste        ,
    setSettingsGtkEnablePrimaryPaste        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkEnablePrimaryPaste           ,
#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.

#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.Surface.surfaceBeep', the windowing system may offer ways to
-- configure the error bell in many ways, such as flashing the
-- window or similar visual effects.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkErrorBellPropertyInfo        ,
#endif
    constructSettingsGtkErrorBell           ,
    getSettingsGtkErrorBell                 ,
    setSettingsGtkErrorBell                 ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkErrorBell                    ,
#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


-- ** 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


-- ** 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.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkKeynavUseCaretPropertyInfo   ,
#endif
    constructSettingsGtkKeynavUseCaret      ,
    getSettingsGtkKeynavUseCaret            ,
    setSettingsGtkKeynavUseCaret            ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkKeynavUseCaret               ,
#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\".

#if defined(ENABLE_OVERLOADING)
    SettingsGtkLongPressTimePropertyInfo    ,
#endif
    constructSettingsGtkLongPressTime       ,
    getSettingsGtkLongPressTime             ,
    setSettingsGtkLongPressTime             ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkLongPressTime                ,
#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.

#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\".

#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.

#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.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkRecentFilesEnabledPropertyInfo,
#endif
    constructSettingsGtkRecentFilesEnabled  ,
    getSettingsGtkRecentFilesEnabled        ,
    setSettingsGtkRecentFilesEnabled        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkRecentFilesEnabled           ,
#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.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkRecentFilesMaxAgePropertyInfo,
#endif
    constructSettingsGtkRecentFilesMaxAge   ,
    getSettingsGtkRecentFilesMaxAge         ,
    setSettingsGtkRecentFilesMaxAge         ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkRecentFilesMaxAge            ,
#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


-- ** 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.

#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


-- ** 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.

#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.

#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.

#if defined(ENABLE_OVERLOADING)
    SettingsGtkTitlebarRightClickPropertyInfo,
#endif
    clearSettingsGtkTitlebarRightClick      ,
    constructSettingsGtkTitlebarRightClick  ,
    getSettingsGtkTitlebarRightClick        ,
    setSettingsGtkTitlebarRightClick        ,
#if defined(ENABLE_OVERLOADING)
    settingsGtkTitlebarRightClick           ,
#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.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider

-- | 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 "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSettingsMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSettingsMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSettingsMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSettingsMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSettingsMethod l o = O.MethodResolutionFailed l o

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

-- 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-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-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-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-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-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-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-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-primary-button-warps-slider"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-primary-button-warps-slider@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkPrimaryButtonWarpsSlider
-- @
getSettingsGtkPrimaryButtonWarpsSlider :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkPrimaryButtonWarpsSlider :: o -> m Bool
getSettingsGtkPrimaryButtonWarpsSlider 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-primary-button-warps-slider"

-- | Set the value of the “@gtk-primary-button-warps-slider@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkPrimaryButtonWarpsSlider 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkPrimaryButtonWarpsSlider :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkPrimaryButtonWarpsSlider :: o -> Bool -> m ()
setSettingsGtkPrimaryButtonWarpsSlider 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-primary-button-warps-slider" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkPrimaryButtonWarpsSliderPropertyInfo
instance AttrInfo SettingsGtkPrimaryButtonWarpsSliderPropertyInfo where
    type AttrAllowedOps SettingsGtkPrimaryButtonWarpsSliderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkPrimaryButtonWarpsSliderPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkPrimaryButtonWarpsSliderPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkPrimaryButtonWarpsSliderPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkPrimaryButtonWarpsSliderPropertyInfo = Bool
    type AttrGetType SettingsGtkPrimaryButtonWarpsSliderPropertyInfo = Bool
    type AttrLabel SettingsGtkPrimaryButtonWarpsSliderPropertyInfo = "gtk-primary-button-warps-slider"
    type AttrOrigin SettingsGtkPrimaryButtonWarpsSliderPropertyInfo = Settings
    attrGet = getSettingsGtkPrimaryButtonWarpsSlider
    attrSet = setSettingsGtkPrimaryButtonWarpsSlider
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkPrimaryButtonWarpsSlider
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-print-backends@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkPrintBackends
-- @
getSettingsGtkPrintBackends :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkPrintBackends :: o -> m (Maybe Text)
getSettingsGtkPrintBackends 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-print-backends"

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

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

-- | Set the value of the “@gtk-print-backends@” 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' #gtkPrintBackends
-- @
clearSettingsGtkPrintBackends :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkPrintBackends :: o -> m ()
clearSettingsGtkPrintBackends 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-print-backends" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkPrintBackendsPropertyInfo
instance AttrInfo SettingsGtkPrintBackendsPropertyInfo where
    type AttrAllowedOps SettingsGtkPrintBackendsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkPrintBackendsPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkPrintBackendsPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkPrintBackendsPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkPrintBackendsPropertyInfo = T.Text
    type AttrGetType SettingsGtkPrintBackendsPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkPrintBackendsPropertyInfo = "gtk-print-backends"
    type AttrOrigin SettingsGtkPrintBackendsPropertyInfo = Settings
    attrGet = getSettingsGtkPrintBackends
    attrSet = setSettingsGtkPrintBackends
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkPrintBackends
    attrClear = clearSettingsGtkPrintBackends
#endif

-- VVV Prop "gtk-print-preview-command"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-print-preview-command@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkPrintPreviewCommand
-- @
getSettingsGtkPrintPreviewCommand :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkPrintPreviewCommand :: o -> m (Maybe Text)
getSettingsGtkPrintPreviewCommand 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-print-preview-command"

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

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

-- | Set the value of the “@gtk-print-preview-command@” 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' #gtkPrintPreviewCommand
-- @
clearSettingsGtkPrintPreviewCommand :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkPrintPreviewCommand :: o -> m ()
clearSettingsGtkPrintPreviewCommand 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-print-preview-command" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkPrintPreviewCommandPropertyInfo
instance AttrInfo SettingsGtkPrintPreviewCommandPropertyInfo where
    type AttrAllowedOps SettingsGtkPrintPreviewCommandPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkPrintPreviewCommandPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkPrintPreviewCommandPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkPrintPreviewCommandPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkPrintPreviewCommandPropertyInfo = T.Text
    type AttrGetType SettingsGtkPrintPreviewCommandPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkPrintPreviewCommandPropertyInfo = "gtk-print-preview-command"
    type AttrOrigin SettingsGtkPrintPreviewCommandPropertyInfo = Settings
    attrGet = getSettingsGtkPrintPreviewCommand
    attrSet = setSettingsGtkPrintPreviewCommand
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkPrintPreviewCommand
    attrClear = clearSettingsGtkPrintPreviewCommand
#endif

-- VVV Prop "gtk-recent-files-enabled"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-recent-files-enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkRecentFilesEnabled
-- @
getSettingsGtkRecentFilesEnabled :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkRecentFilesEnabled :: o -> m Bool
getSettingsGtkRecentFilesEnabled 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-recent-files-enabled"

-- | Set the value of the “@gtk-recent-files-enabled@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkRecentFilesEnabled 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkRecentFilesEnabled :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkRecentFilesEnabled :: o -> Bool -> m ()
setSettingsGtkRecentFilesEnabled 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-recent-files-enabled" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkRecentFilesEnabledPropertyInfo
instance AttrInfo SettingsGtkRecentFilesEnabledPropertyInfo where
    type AttrAllowedOps SettingsGtkRecentFilesEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkRecentFilesEnabledPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkRecentFilesEnabledPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkRecentFilesEnabledPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkRecentFilesEnabledPropertyInfo = Bool
    type AttrGetType SettingsGtkRecentFilesEnabledPropertyInfo = Bool
    type AttrLabel SettingsGtkRecentFilesEnabledPropertyInfo = "gtk-recent-files-enabled"
    type AttrOrigin SettingsGtkRecentFilesEnabledPropertyInfo = Settings
    attrGet = getSettingsGtkRecentFilesEnabled
    attrSet = setSettingsGtkRecentFilesEnabled
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkRecentFilesEnabled
    attrClear = undefined
#endif

-- VVV Prop "gtk-recent-files-max-age"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-recent-files-max-age@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkRecentFilesMaxAge
-- @
getSettingsGtkRecentFilesMaxAge :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsGtkRecentFilesMaxAge :: o -> m Int32
getSettingsGtkRecentFilesMaxAge 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-recent-files-max-age"

-- | Set the value of the “@gtk-recent-files-max-age@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkRecentFilesMaxAge 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkRecentFilesMaxAge :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsGtkRecentFilesMaxAge :: o -> Int32 -> m ()
setSettingsGtkRecentFilesMaxAge 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-recent-files-max-age" Int32
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkRecentFilesMaxAgePropertyInfo
instance AttrInfo SettingsGtkRecentFilesMaxAgePropertyInfo where
    type AttrAllowedOps SettingsGtkRecentFilesMaxAgePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkRecentFilesMaxAgePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkRecentFilesMaxAgePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkRecentFilesMaxAgePropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkRecentFilesMaxAgePropertyInfo = Int32
    type AttrGetType SettingsGtkRecentFilesMaxAgePropertyInfo = Int32
    type AttrLabel SettingsGtkRecentFilesMaxAgePropertyInfo = "gtk-recent-files-max-age"
    type AttrOrigin SettingsGtkRecentFilesMaxAgePropertyInfo = Settings
    attrGet = getSettingsGtkRecentFilesMaxAge
    attrSet = setSettingsGtkRecentFilesMaxAge
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkRecentFilesMaxAge
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-shell-shows-app-menu@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkShellShowsAppMenu
-- @
getSettingsGtkShellShowsAppMenu :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkShellShowsAppMenu :: o -> m Bool
getSettingsGtkShellShowsAppMenu 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-shell-shows-app-menu"

-- | Set the value of the “@gtk-shell-shows-app-menu@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkShellShowsAppMenu 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkShellShowsAppMenu :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkShellShowsAppMenu :: o -> Bool -> m ()
setSettingsGtkShellShowsAppMenu 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-shell-shows-app-menu" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkShellShowsAppMenuPropertyInfo
instance AttrInfo SettingsGtkShellShowsAppMenuPropertyInfo where
    type AttrAllowedOps SettingsGtkShellShowsAppMenuPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkShellShowsAppMenuPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkShellShowsAppMenuPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkShellShowsAppMenuPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkShellShowsAppMenuPropertyInfo = Bool
    type AttrGetType SettingsGtkShellShowsAppMenuPropertyInfo = Bool
    type AttrLabel SettingsGtkShellShowsAppMenuPropertyInfo = "gtk-shell-shows-app-menu"
    type AttrOrigin SettingsGtkShellShowsAppMenuPropertyInfo = Settings
    attrGet = getSettingsGtkShellShowsAppMenu
    attrSet = setSettingsGtkShellShowsAppMenu
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkShellShowsAppMenu
    attrClear = undefined
#endif

-- VVV Prop "gtk-shell-shows-desktop"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-shell-shows-desktop@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkShellShowsDesktop
-- @
getSettingsGtkShellShowsDesktop :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkShellShowsDesktop :: o -> m Bool
getSettingsGtkShellShowsDesktop 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-shell-shows-desktop"

-- | Set the value of the “@gtk-shell-shows-desktop@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkShellShowsDesktop 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkShellShowsDesktop :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkShellShowsDesktop :: o -> Bool -> m ()
setSettingsGtkShellShowsDesktop 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-shell-shows-desktop" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkShellShowsDesktopPropertyInfo
instance AttrInfo SettingsGtkShellShowsDesktopPropertyInfo where
    type AttrAllowedOps SettingsGtkShellShowsDesktopPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkShellShowsDesktopPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkShellShowsDesktopPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkShellShowsDesktopPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkShellShowsDesktopPropertyInfo = Bool
    type AttrGetType SettingsGtkShellShowsDesktopPropertyInfo = Bool
    type AttrLabel SettingsGtkShellShowsDesktopPropertyInfo = "gtk-shell-shows-desktop"
    type AttrOrigin SettingsGtkShellShowsDesktopPropertyInfo = Settings
    attrGet = getSettingsGtkShellShowsDesktop
    attrSet = setSettingsGtkShellShowsDesktop
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkShellShowsDesktop
    attrClear = undefined
#endif

-- VVV Prop "gtk-shell-shows-menubar"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-shell-shows-menubar@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkShellShowsMenubar
-- @
getSettingsGtkShellShowsMenubar :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkShellShowsMenubar :: o -> m Bool
getSettingsGtkShellShowsMenubar 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-shell-shows-menubar"

-- | Set the value of the “@gtk-shell-shows-menubar@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkShellShowsMenubar 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkShellShowsMenubar :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkShellShowsMenubar :: o -> Bool -> m ()
setSettingsGtkShellShowsMenubar 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-shell-shows-menubar" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkShellShowsMenubarPropertyInfo
instance AttrInfo SettingsGtkShellShowsMenubarPropertyInfo where
    type AttrAllowedOps SettingsGtkShellShowsMenubarPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkShellShowsMenubarPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkShellShowsMenubarPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SettingsGtkShellShowsMenubarPropertyInfo = (~) Bool
    type AttrTransferType SettingsGtkShellShowsMenubarPropertyInfo = Bool
    type AttrGetType SettingsGtkShellShowsMenubarPropertyInfo = Bool
    type AttrLabel SettingsGtkShellShowsMenubarPropertyInfo = "gtk-shell-shows-menubar"
    type AttrOrigin SettingsGtkShellShowsMenubarPropertyInfo = Settings
    attrGet = getSettingsGtkShellShowsMenubar
    attrSet = setSettingsGtkShellShowsMenubar
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkShellShowsMenubar
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-sound-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 #gtkSoundThemeName
-- @
getSettingsGtkSoundThemeName :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkSoundThemeName :: o -> m (Maybe Text)
getSettingsGtkSoundThemeName 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-sound-theme-name"

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

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

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

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

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

-- | Get the value of the “@gtk-split-cursor@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkSplitCursor
-- @
getSettingsGtkSplitCursor :: (MonadIO m, IsSettings o) => o -> m Bool
getSettingsGtkSplitCursor :: o -> m Bool
getSettingsGtkSplitCursor 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-split-cursor"

-- | Set the value of the “@gtk-split-cursor@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkSplitCursor 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkSplitCursor :: (MonadIO m, IsSettings o) => o -> Bool -> m ()
setSettingsGtkSplitCursor :: o -> Bool -> m ()
setSettingsGtkSplitCursor 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-split-cursor" Bool
val

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

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

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

-- | Get the value of the “@gtk-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 #gtkThemeName
-- @
getSettingsGtkThemeName :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkThemeName :: o -> m (Maybe Text)
getSettingsGtkThemeName 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-theme-name"

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

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

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

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

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

-- | Get the value of the “@gtk-titlebar-double-click@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkTitlebarDoubleClick
-- @
getSettingsGtkTitlebarDoubleClick :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkTitlebarDoubleClick :: o -> m (Maybe Text)
getSettingsGtkTitlebarDoubleClick 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-titlebar-double-click"

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

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

-- | Set the value of the “@gtk-titlebar-double-click@” 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' #gtkTitlebarDoubleClick
-- @
clearSettingsGtkTitlebarDoubleClick :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkTitlebarDoubleClick :: o -> m ()
clearSettingsGtkTitlebarDoubleClick 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-titlebar-double-click" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkTitlebarDoubleClickPropertyInfo
instance AttrInfo SettingsGtkTitlebarDoubleClickPropertyInfo where
    type AttrAllowedOps SettingsGtkTitlebarDoubleClickPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkTitlebarDoubleClickPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkTitlebarDoubleClickPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkTitlebarDoubleClickPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkTitlebarDoubleClickPropertyInfo = T.Text
    type AttrGetType SettingsGtkTitlebarDoubleClickPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkTitlebarDoubleClickPropertyInfo = "gtk-titlebar-double-click"
    type AttrOrigin SettingsGtkTitlebarDoubleClickPropertyInfo = Settings
    attrGet = getSettingsGtkTitlebarDoubleClick
    attrSet = setSettingsGtkTitlebarDoubleClick
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkTitlebarDoubleClick
    attrClear = clearSettingsGtkTitlebarDoubleClick
#endif

-- VVV Prop "gtk-titlebar-middle-click"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-titlebar-middle-click@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkTitlebarMiddleClick
-- @
getSettingsGtkTitlebarMiddleClick :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkTitlebarMiddleClick :: o -> m (Maybe Text)
getSettingsGtkTitlebarMiddleClick 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-titlebar-middle-click"

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

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

-- | Set the value of the “@gtk-titlebar-middle-click@” 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' #gtkTitlebarMiddleClick
-- @
clearSettingsGtkTitlebarMiddleClick :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkTitlebarMiddleClick :: o -> m ()
clearSettingsGtkTitlebarMiddleClick 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-titlebar-middle-click" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkTitlebarMiddleClickPropertyInfo
instance AttrInfo SettingsGtkTitlebarMiddleClickPropertyInfo where
    type AttrAllowedOps SettingsGtkTitlebarMiddleClickPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkTitlebarMiddleClickPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkTitlebarMiddleClickPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkTitlebarMiddleClickPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkTitlebarMiddleClickPropertyInfo = T.Text
    type AttrGetType SettingsGtkTitlebarMiddleClickPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkTitlebarMiddleClickPropertyInfo = "gtk-titlebar-middle-click"
    type AttrOrigin SettingsGtkTitlebarMiddleClickPropertyInfo = Settings
    attrGet = getSettingsGtkTitlebarMiddleClick
    attrSet = setSettingsGtkTitlebarMiddleClick
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkTitlebarMiddleClick
    attrClear = clearSettingsGtkTitlebarMiddleClick
#endif

-- VVV Prop "gtk-titlebar-right-click"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@gtk-titlebar-right-click@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkTitlebarRightClick
-- @
getSettingsGtkTitlebarRightClick :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkTitlebarRightClick :: o -> m (Maybe Text)
getSettingsGtkTitlebarRightClick 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-titlebar-right-click"

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

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

-- | Set the value of the “@gtk-titlebar-right-click@” 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' #gtkTitlebarRightClick
-- @
clearSettingsGtkTitlebarRightClick :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkTitlebarRightClick :: o -> m ()
clearSettingsGtkTitlebarRightClick 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-titlebar-right-click" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkTitlebarRightClickPropertyInfo
instance AttrInfo SettingsGtkTitlebarRightClickPropertyInfo where
    type AttrAllowedOps SettingsGtkTitlebarRightClickPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkTitlebarRightClickPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkTitlebarRightClickPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkTitlebarRightClickPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkTitlebarRightClickPropertyInfo = T.Text
    type AttrGetType SettingsGtkTitlebarRightClickPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkTitlebarRightClickPropertyInfo = "gtk-titlebar-right-click"
    type AttrOrigin SettingsGtkTitlebarRightClickPropertyInfo = Settings
    attrGet = getSettingsGtkTitlebarRightClick
    attrSet = setSettingsGtkTitlebarRightClick
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkTitlebarRightClick
    attrClear = clearSettingsGtkTitlebarRightClick
#endif

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

-- | Get the value of the “@gtk-xft-antialias@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkXftAntialias
-- @
getSettingsGtkXftAntialias :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsGtkXftAntialias :: o -> m Int32
getSettingsGtkXftAntialias 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-xft-antialias"

-- | Set the value of the “@gtk-xft-antialias@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkXftAntialias 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkXftAntialias :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsGtkXftAntialias :: o -> Int32 -> m ()
setSettingsGtkXftAntialias 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-xft-antialias" Int32
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkXftAntialiasPropertyInfo
instance AttrInfo SettingsGtkXftAntialiasPropertyInfo where
    type AttrAllowedOps SettingsGtkXftAntialiasPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkXftAntialiasPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkXftAntialiasPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkXftAntialiasPropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkXftAntialiasPropertyInfo = Int32
    type AttrGetType SettingsGtkXftAntialiasPropertyInfo = Int32
    type AttrLabel SettingsGtkXftAntialiasPropertyInfo = "gtk-xft-antialias"
    type AttrOrigin SettingsGtkXftAntialiasPropertyInfo = Settings
    attrGet = getSettingsGtkXftAntialias
    attrSet = setSettingsGtkXftAntialias
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkXftAntialias
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-xft-dpi@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkXftDpi
-- @
getSettingsGtkXftDpi :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsGtkXftDpi :: o -> m Int32
getSettingsGtkXftDpi 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-xft-dpi"

-- | Set the value of the “@gtk-xft-dpi@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkXftDpi 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkXftDpi :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsGtkXftDpi :: o -> Int32 -> m ()
setSettingsGtkXftDpi 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-xft-dpi" Int32
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkXftDpiPropertyInfo
instance AttrInfo SettingsGtkXftDpiPropertyInfo where
    type AttrAllowedOps SettingsGtkXftDpiPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkXftDpiPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkXftDpiPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkXftDpiPropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkXftDpiPropertyInfo = Int32
    type AttrGetType SettingsGtkXftDpiPropertyInfo = Int32
    type AttrLabel SettingsGtkXftDpiPropertyInfo = "gtk-xft-dpi"
    type AttrOrigin SettingsGtkXftDpiPropertyInfo = Settings
    attrGet = getSettingsGtkXftDpi
    attrSet = setSettingsGtkXftDpi
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkXftDpi
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-xft-hinting@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkXftHinting
-- @
getSettingsGtkXftHinting :: (MonadIO m, IsSettings o) => o -> m Int32
getSettingsGtkXftHinting :: o -> m Int32
getSettingsGtkXftHinting 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-xft-hinting"

-- | Set the value of the “@gtk-xft-hinting@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' settings [ #gtkXftHinting 'Data.GI.Base.Attributes.:=' value ]
-- @
setSettingsGtkXftHinting :: (MonadIO m, IsSettings o) => o -> Int32 -> m ()
setSettingsGtkXftHinting :: o -> Int32 -> m ()
setSettingsGtkXftHinting 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-xft-hinting" Int32
val

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

#if defined(ENABLE_OVERLOADING)
data SettingsGtkXftHintingPropertyInfo
instance AttrInfo SettingsGtkXftHintingPropertyInfo where
    type AttrAllowedOps SettingsGtkXftHintingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SettingsGtkXftHintingPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkXftHintingPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint SettingsGtkXftHintingPropertyInfo = (~) Int32
    type AttrTransferType SettingsGtkXftHintingPropertyInfo = Int32
    type AttrGetType SettingsGtkXftHintingPropertyInfo = Int32
    type AttrLabel SettingsGtkXftHintingPropertyInfo = "gtk-xft-hinting"
    type AttrOrigin SettingsGtkXftHintingPropertyInfo = Settings
    attrGet = getSettingsGtkXftHinting
    attrSet = setSettingsGtkXftHinting
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkXftHinting
    attrClear = undefined
#endif

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

-- | Get the value of the “@gtk-xft-hintstyle@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkXftHintstyle
-- @
getSettingsGtkXftHintstyle :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkXftHintstyle :: o -> m (Maybe Text)
getSettingsGtkXftHintstyle 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-xft-hintstyle"

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

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

-- | Set the value of the “@gtk-xft-hintstyle@” 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' #gtkXftHintstyle
-- @
clearSettingsGtkXftHintstyle :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkXftHintstyle :: o -> m ()
clearSettingsGtkXftHintstyle 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-xft-hintstyle" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkXftHintstylePropertyInfo
instance AttrInfo SettingsGtkXftHintstylePropertyInfo where
    type AttrAllowedOps SettingsGtkXftHintstylePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkXftHintstylePropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkXftHintstylePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkXftHintstylePropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkXftHintstylePropertyInfo = T.Text
    type AttrGetType SettingsGtkXftHintstylePropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkXftHintstylePropertyInfo = "gtk-xft-hintstyle"
    type AttrOrigin SettingsGtkXftHintstylePropertyInfo = Settings
    attrGet = getSettingsGtkXftHintstyle
    attrSet = setSettingsGtkXftHintstyle
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkXftHintstyle
    attrClear = clearSettingsGtkXftHintstyle
#endif

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

-- | Get the value of the “@gtk-xft-rgba@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' settings #gtkXftRgba
-- @
getSettingsGtkXftRgba :: (MonadIO m, IsSettings o) => o -> m (Maybe T.Text)
getSettingsGtkXftRgba :: o -> m (Maybe Text)
getSettingsGtkXftRgba 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-xft-rgba"

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

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

-- | Set the value of the “@gtk-xft-rgba@” 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' #gtkXftRgba
-- @
clearSettingsGtkXftRgba :: (MonadIO m, IsSettings o) => o -> m ()
clearSettingsGtkXftRgba :: o -> m ()
clearSettingsGtkXftRgba 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-xft-rgba" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data SettingsGtkXftRgbaPropertyInfo
instance AttrInfo SettingsGtkXftRgbaPropertyInfo where
    type AttrAllowedOps SettingsGtkXftRgbaPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SettingsGtkXftRgbaPropertyInfo = IsSettings
    type AttrSetTypeConstraint SettingsGtkXftRgbaPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SettingsGtkXftRgbaPropertyInfo = (~) T.Text
    type AttrTransferType SettingsGtkXftRgbaPropertyInfo = T.Text
    type AttrGetType SettingsGtkXftRgbaPropertyInfo = (Maybe T.Text)
    type AttrLabel SettingsGtkXftRgbaPropertyInfo = "gtk-xft-rgba"
    type AttrOrigin SettingsGtkXftRgbaPropertyInfo = Settings
    attrGet = getSettingsGtkXftRgba
    attrSet = setSettingsGtkXftRgba
    attrTransfer _ v = do
        return v
    attrConstruct = constructSettingsGtkXftRgba
    attrClear = clearSettingsGtkXftRgba
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Settings
type instance O.AttributeList Settings = SettingsAttributeList
type SettingsAttributeList = ('[ '("gtkAlternativeButtonOrder", SettingsGtkAlternativeButtonOrderPropertyInfo), '("gtkAlternativeSortArrows", SettingsGtkAlternativeSortArrowsPropertyInfo), '("gtkApplicationPreferDarkTheme", SettingsGtkApplicationPreferDarkThemePropertyInfo), '("gtkCursorBlink", SettingsGtkCursorBlinkPropertyInfo), '("gtkCursorBlinkTime", SettingsGtkCursorBlinkTimePropertyInfo), '("gtkCursorBlinkTimeout", SettingsGtkCursorBlinkTimeoutPropertyInfo), '("gtkCursorThemeName", SettingsGtkCursorThemeNamePropertyInfo), '("gtkCursorThemeSize", SettingsGtkCursorThemeSizePropertyInfo), '("gtkDecorationLayout", SettingsGtkDecorationLayoutPropertyInfo), '("gtkDialogsUseHeader", SettingsGtkDialogsUseHeaderPropertyInfo), '("gtkDndDragThreshold", SettingsGtkDndDragThresholdPropertyInfo), '("gtkDoubleClickDistance", SettingsGtkDoubleClickDistancePropertyInfo), '("gtkDoubleClickTime", SettingsGtkDoubleClickTimePropertyInfo), '("gtkEnableAccels", SettingsGtkEnableAccelsPropertyInfo), '("gtkEnableAnimations", SettingsGtkEnableAnimationsPropertyInfo), '("gtkEnableEventSounds", SettingsGtkEnableEventSoundsPropertyInfo), '("gtkEnableInputFeedbackSounds", SettingsGtkEnableInputFeedbackSoundsPropertyInfo), '("gtkEnablePrimaryPaste", SettingsGtkEnablePrimaryPastePropertyInfo), '("gtkEntryPasswordHintTimeout", SettingsGtkEntryPasswordHintTimeoutPropertyInfo), '("gtkEntrySelectOnFocus", SettingsGtkEntrySelectOnFocusPropertyInfo), '("gtkErrorBell", SettingsGtkErrorBellPropertyInfo), '("gtkFontName", SettingsGtkFontNamePropertyInfo), '("gtkFontconfigTimestamp", SettingsGtkFontconfigTimestampPropertyInfo), '("gtkIconThemeName", SettingsGtkIconThemeNamePropertyInfo), '("gtkImModule", SettingsGtkImModulePropertyInfo), '("gtkKeynavUseCaret", SettingsGtkKeynavUseCaretPropertyInfo), '("gtkLabelSelectOnFocus", SettingsGtkLabelSelectOnFocusPropertyInfo), '("gtkLongPressTime", SettingsGtkLongPressTimePropertyInfo), '("gtkPrimaryButtonWarpsSlider", SettingsGtkPrimaryButtonWarpsSliderPropertyInfo), '("gtkPrintBackends", SettingsGtkPrintBackendsPropertyInfo), '("gtkPrintPreviewCommand", SettingsGtkPrintPreviewCommandPropertyInfo), '("gtkRecentFilesEnabled", SettingsGtkRecentFilesEnabledPropertyInfo), '("gtkRecentFilesMaxAge", SettingsGtkRecentFilesMaxAgePropertyInfo), '("gtkShellShowsAppMenu", SettingsGtkShellShowsAppMenuPropertyInfo), '("gtkShellShowsDesktop", SettingsGtkShellShowsDesktopPropertyInfo), '("gtkShellShowsMenubar", SettingsGtkShellShowsMenubarPropertyInfo), '("gtkSoundThemeName", SettingsGtkSoundThemeNamePropertyInfo), '("gtkSplitCursor", SettingsGtkSplitCursorPropertyInfo), '("gtkThemeName", SettingsGtkThemeNamePropertyInfo), '("gtkTitlebarDoubleClick", SettingsGtkTitlebarDoubleClickPropertyInfo), '("gtkTitlebarMiddleClick", SettingsGtkTitlebarMiddleClickPropertyInfo), '("gtkTitlebarRightClick", SettingsGtkTitlebarRightClickPropertyInfo), '("gtkXftAntialias", SettingsGtkXftAntialiasPropertyInfo), '("gtkXftDpi", SettingsGtkXftDpiPropertyInfo), '("gtkXftHinting", SettingsGtkXftHintingPropertyInfo), '("gtkXftHintstyle", SettingsGtkXftHintstylePropertyInfo), '("gtkXftRgba", SettingsGtkXftRgbaPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
settingsGtkAlternativeButtonOrder :: AttrLabelProxy "gtkAlternativeButtonOrder"
settingsGtkAlternativeButtonOrder = AttrLabelProxy

settingsGtkAlternativeSortArrows :: AttrLabelProxy "gtkAlternativeSortArrows"
settingsGtkAlternativeSortArrows = AttrLabelProxy

settingsGtkApplicationPreferDarkTheme :: AttrLabelProxy "gtkApplicationPreferDarkTheme"
settingsGtkApplicationPreferDarkTheme = AttrLabelProxy

settingsGtkCursorBlink :: AttrLabelProxy "gtkCursorBlink"
settingsGtkCursorBlink = AttrLabelProxy

settingsGtkCursorBlinkTime :: AttrLabelProxy "gtkCursorBlinkTime"
settingsGtkCursorBlinkTime = AttrLabelProxy

settingsGtkCursorBlinkTimeout :: AttrLabelProxy "gtkCursorBlinkTimeout"
settingsGtkCursorBlinkTimeout = AttrLabelProxy

settingsGtkCursorThemeName :: AttrLabelProxy "gtkCursorThemeName"
settingsGtkCursorThemeName = AttrLabelProxy

settingsGtkCursorThemeSize :: AttrLabelProxy "gtkCursorThemeSize"
settingsGtkCursorThemeSize = AttrLabelProxy

settingsGtkDecorationLayout :: AttrLabelProxy "gtkDecorationLayout"
settingsGtkDecorationLayout = AttrLabelProxy

settingsGtkDialogsUseHeader :: AttrLabelProxy "gtkDialogsUseHeader"
settingsGtkDialogsUseHeader = AttrLabelProxy

settingsGtkDndDragThreshold :: AttrLabelProxy "gtkDndDragThreshold"
settingsGtkDndDragThreshold = AttrLabelProxy

settingsGtkDoubleClickDistance :: AttrLabelProxy "gtkDoubleClickDistance"
settingsGtkDoubleClickDistance = AttrLabelProxy

settingsGtkDoubleClickTime :: AttrLabelProxy "gtkDoubleClickTime"
settingsGtkDoubleClickTime = AttrLabelProxy

settingsGtkEnableAccels :: AttrLabelProxy "gtkEnableAccels"
settingsGtkEnableAccels = AttrLabelProxy

settingsGtkEnableAnimations :: AttrLabelProxy "gtkEnableAnimations"
settingsGtkEnableAnimations = AttrLabelProxy

settingsGtkEnableEventSounds :: AttrLabelProxy "gtkEnableEventSounds"
settingsGtkEnableEventSounds = AttrLabelProxy

settingsGtkEnableInputFeedbackSounds :: AttrLabelProxy "gtkEnableInputFeedbackSounds"
settingsGtkEnableInputFeedbackSounds = AttrLabelProxy

settingsGtkEnablePrimaryPaste :: AttrLabelProxy "gtkEnablePrimaryPaste"
settingsGtkEnablePrimaryPaste = AttrLabelProxy

settingsGtkEntryPasswordHintTimeout :: AttrLabelProxy "gtkEntryPasswordHintTimeout"
settingsGtkEntryPasswordHintTimeout = AttrLabelProxy

settingsGtkEntrySelectOnFocus :: AttrLabelProxy "gtkEntrySelectOnFocus"
settingsGtkEntrySelectOnFocus = AttrLabelProxy

settingsGtkErrorBell :: AttrLabelProxy "gtkErrorBell"
settingsGtkErrorBell = AttrLabelProxy

settingsGtkFontName :: AttrLabelProxy "gtkFontName"
settingsGtkFontName = AttrLabelProxy

settingsGtkFontconfigTimestamp :: AttrLabelProxy "gtkFontconfigTimestamp"
settingsGtkFontconfigTimestamp = AttrLabelProxy

settingsGtkIconThemeName :: AttrLabelProxy "gtkIconThemeName"
settingsGtkIconThemeName = AttrLabelProxy

settingsGtkImModule :: AttrLabelProxy "gtkImModule"
settingsGtkImModule = AttrLabelProxy

settingsGtkKeynavUseCaret :: AttrLabelProxy "gtkKeynavUseCaret"
settingsGtkKeynavUseCaret = AttrLabelProxy

settingsGtkLabelSelectOnFocus :: AttrLabelProxy "gtkLabelSelectOnFocus"
settingsGtkLabelSelectOnFocus = AttrLabelProxy

settingsGtkLongPressTime :: AttrLabelProxy "gtkLongPressTime"
settingsGtkLongPressTime = AttrLabelProxy

settingsGtkPrimaryButtonWarpsSlider :: AttrLabelProxy "gtkPrimaryButtonWarpsSlider"
settingsGtkPrimaryButtonWarpsSlider = AttrLabelProxy

settingsGtkPrintBackends :: AttrLabelProxy "gtkPrintBackends"
settingsGtkPrintBackends = AttrLabelProxy

settingsGtkPrintPreviewCommand :: AttrLabelProxy "gtkPrintPreviewCommand"
settingsGtkPrintPreviewCommand = AttrLabelProxy

settingsGtkRecentFilesEnabled :: AttrLabelProxy "gtkRecentFilesEnabled"
settingsGtkRecentFilesEnabled = AttrLabelProxy

settingsGtkRecentFilesMaxAge :: AttrLabelProxy "gtkRecentFilesMaxAge"
settingsGtkRecentFilesMaxAge = AttrLabelProxy

settingsGtkShellShowsAppMenu :: AttrLabelProxy "gtkShellShowsAppMenu"
settingsGtkShellShowsAppMenu = AttrLabelProxy

settingsGtkShellShowsDesktop :: AttrLabelProxy "gtkShellShowsDesktop"
settingsGtkShellShowsDesktop = AttrLabelProxy

settingsGtkShellShowsMenubar :: AttrLabelProxy "gtkShellShowsMenubar"
settingsGtkShellShowsMenubar = AttrLabelProxy

settingsGtkSoundThemeName :: AttrLabelProxy "gtkSoundThemeName"
settingsGtkSoundThemeName = AttrLabelProxy

settingsGtkSplitCursor :: AttrLabelProxy "gtkSplitCursor"
settingsGtkSplitCursor = AttrLabelProxy

settingsGtkThemeName :: AttrLabelProxy "gtkThemeName"
settingsGtkThemeName = AttrLabelProxy

settingsGtkTitlebarDoubleClick :: AttrLabelProxy "gtkTitlebarDoubleClick"
settingsGtkTitlebarDoubleClick = AttrLabelProxy

settingsGtkTitlebarMiddleClick :: AttrLabelProxy "gtkTitlebarMiddleClick"
settingsGtkTitlebarMiddleClick = AttrLabelProxy

settingsGtkTitlebarRightClick :: AttrLabelProxy "gtkTitlebarRightClick"
settingsGtkTitlebarRightClick = AttrLabelProxy

settingsGtkXftAntialias :: AttrLabelProxy "gtkXftAntialias"
settingsGtkXftAntialias = AttrLabelProxy

settingsGtkXftDpi :: AttrLabelProxy "gtkXftDpi"
settingsGtkXftDpi = AttrLabelProxy

settingsGtkXftHinting :: AttrLabelProxy "gtkXftHinting"
settingsGtkXftHinting = AttrLabelProxy

settingsGtkXftHintstyle :: AttrLabelProxy "gtkXftHintstyle"
settingsGtkXftHintstyle = AttrLabelProxy

settingsGtkXftRgba :: AttrLabelProxy "gtkXftRgba"
settingsGtkXftRgba = AttrLabelProxy

#endif

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

#endif

-- method Settings::reset_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Settings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSettings object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the setting to reset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_settings_reset_property" gtk_settings_reset_property :: 
    Ptr Settings ->                         -- settings : TInterface (Name {namespace = "Gtk", name = "Settings"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Undoes the effect of calling @/g_object_set()/@ to install an
-- application-specific value for a setting. After this call,
-- the setting will again follow the session-wide value for
-- this setting.
settingsResetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.Settings.Settings' object
    -> T.Text
    -- ^ /@name@/: the name of the setting to reset
    -> m ()
settingsResetProperty :: a -> Text -> m ()
settingsResetProperty settings :: a
settings name :: Text
name = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Settings
settings' <- a -> IO (Ptr Settings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr Settings -> CString -> IO ()
gtk_settings_reset_property Ptr Settings
settings' CString
name'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SettingsResetPropertyMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSettings a) => O.MethodInfo SettingsResetPropertyMethodInfo a signature where
    overloadedMethod = settingsResetProperty

#endif

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

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

-- | Gets the t'GI.Gtk.Objects.Settings.Settings' object for the default display, creating
-- it if necessary. See 'GI.Gtk.Objects.Settings.settingsGetForDisplay'.
settingsGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m (Maybe Settings)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.Settings.Settings' object. If there is
    -- no default display, then returns 'P.Nothing'.
settingsGetDefault :: m (Maybe Settings)
settingsGetDefault  = IO (Maybe Settings) -> m (Maybe Settings)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Settings) -> m (Maybe Settings))
-> IO (Maybe Settings) -> m (Maybe Settings)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Settings
result <- IO (Ptr Settings)
gtk_settings_get_default
    Maybe Settings
maybeResult <- Ptr Settings
-> (Ptr Settings -> IO Settings) -> IO (Maybe Settings)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Settings
result ((Ptr Settings -> IO Settings) -> IO (Maybe Settings))
-> (Ptr Settings -> IO Settings) -> IO (Maybe Settings)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Settings
result' -> do
        Settings
result'' <- ((ManagedPtr Settings -> Settings) -> Ptr Settings -> IO Settings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Settings -> Settings
Settings) Ptr Settings
result'
        Settings -> IO Settings
forall (m :: * -> *) a. Monad m => a -> m a
return Settings
result''
    Maybe Settings -> IO (Maybe Settings)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Settings
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method Settings::get_for_display
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Settings" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_settings_get_for_display" gtk_settings_get_for_display :: 
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Settings)

-- | Gets the t'GI.Gtk.Objects.Settings.Settings' object for /@display@/, creating it if necessary.
settingsGetForDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'.
    -> m Settings
    -- ^ __Returns:__ a t'GI.Gtk.Objects.Settings.Settings' object.
settingsGetForDisplay :: a -> m Settings
settingsGetForDisplay display :: a
display = IO Settings -> m Settings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Settings -> m Settings) -> IO Settings -> m Settings
forall a b. (a -> b) -> a -> b
$ do
    Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
    Ptr Settings
result <- Ptr Display -> IO (Ptr Settings)
gtk_settings_get_for_display Ptr Display
display'
    Text -> Ptr Settings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "settingsGetForDisplay" Ptr Settings
result
    Settings
result' <- ((ManagedPtr Settings -> Settings) -> Ptr Settings -> IO Settings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Settings -> Settings
Settings) Ptr Settings
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
    Settings -> IO Settings
forall (m :: * -> *) a. Monad m => a -> m a
return Settings
result'

#if defined(ENABLE_OVERLOADING)
#endif