{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A page from [class/@preferencesWindow@/].
-- 
-- The @HdyPreferencesPage@ widget gathers preferences groups into a single page
-- of a preferences window.
-- 
-- == CSS nodes
-- 
-- @HdyPreferencesPage@ has a single CSS node with name @preferencespage@.
-- 
-- /Since: 1.0/

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

module GI.Handy.Objects.PreferencesPage
    ( 

-- * Exported types
    PreferencesPage(..)                     ,
    IsPreferencesPage                       ,
    toPreferencesPage                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [add]("GI.Gtk.Objects.Container#g:method:add"), [addAccelerator]("GI.Gtk.Objects.Widget#g:method:addAccelerator"), [addChild]("GI.Gtk.Interfaces.Buildable#g:method:addChild"), [addDeviceEvents]("GI.Gtk.Objects.Widget#g:method:addDeviceEvents"), [addEvents]("GI.Gtk.Objects.Widget#g:method:addEvents"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [canActivateAccel]("GI.Gtk.Objects.Widget#g:method:canActivateAccel"), [checkResize]("GI.Gtk.Objects.Container#g:method:checkResize"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [childGetProperty]("GI.Gtk.Objects.Container#g:method:childGetProperty"), [childNotify]("GI.Gtk.Objects.Container#g:method:childNotify"), [childNotifyByPspec]("GI.Gtk.Objects.Container#g:method:childNotifyByPspec"), [childSetProperty]("GI.Gtk.Objects.Container#g:method:childSetProperty"), [childType]("GI.Gtk.Objects.Container#g:method:childType"), [classPath]("GI.Gtk.Objects.Widget#g:method:classPath"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [constructChild]("GI.Gtk.Interfaces.Buildable#g:method:constructChild"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [customFinished]("GI.Gtk.Interfaces.Buildable#g:method:customFinished"), [customTagEnd]("GI.Gtk.Interfaces.Buildable#g:method:customTagEnd"), [customTagStart]("GI.Gtk.Interfaces.Buildable#g:method:customTagStart"), [destroy]("GI.Gtk.Objects.Widget#g:method:destroy"), [destroyed]("GI.Gtk.Objects.Widget#g:method:destroyed"), [deviceIsShadowed]("GI.Gtk.Objects.Widget#g:method:deviceIsShadowed"), [dragBegin]("GI.Gtk.Objects.Widget#g:method:dragBegin"), [dragBeginWithCoordinates]("GI.Gtk.Objects.Widget#g:method:dragBeginWithCoordinates"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [dragDestAddImageTargets]("GI.Gtk.Objects.Widget#g:method:dragDestAddImageTargets"), [dragDestAddTextTargets]("GI.Gtk.Objects.Widget#g:method:dragDestAddTextTargets"), [dragDestAddUriTargets]("GI.Gtk.Objects.Widget#g:method:dragDestAddUriTargets"), [dragDestFindTarget]("GI.Gtk.Objects.Widget#g:method:dragDestFindTarget"), [dragDestGetTargetList]("GI.Gtk.Objects.Widget#g:method:dragDestGetTargetList"), [dragDestGetTrackMotion]("GI.Gtk.Objects.Widget#g:method:dragDestGetTrackMotion"), [dragDestSet]("GI.Gtk.Objects.Widget#g:method:dragDestSet"), [dragDestSetProxy]("GI.Gtk.Objects.Widget#g:method:dragDestSetProxy"), [dragDestSetTargetList]("GI.Gtk.Objects.Widget#g:method:dragDestSetTargetList"), [dragDestSetTrackMotion]("GI.Gtk.Objects.Widget#g:method:dragDestSetTrackMotion"), [dragDestUnset]("GI.Gtk.Objects.Widget#g:method:dragDestUnset"), [dragGetData]("GI.Gtk.Objects.Widget#g:method:dragGetData"), [dragHighlight]("GI.Gtk.Objects.Widget#g:method:dragHighlight"), [dragSourceAddImageTargets]("GI.Gtk.Objects.Widget#g:method:dragSourceAddImageTargets"), [dragSourceAddTextTargets]("GI.Gtk.Objects.Widget#g:method:dragSourceAddTextTargets"), [dragSourceAddUriTargets]("GI.Gtk.Objects.Widget#g:method:dragSourceAddUriTargets"), [dragSourceGetTargetList]("GI.Gtk.Objects.Widget#g:method:dragSourceGetTargetList"), [dragSourceSet]("GI.Gtk.Objects.Widget#g:method:dragSourceSet"), [dragSourceSetIconGicon]("GI.Gtk.Objects.Widget#g:method:dragSourceSetIconGicon"), [dragSourceSetIconName]("GI.Gtk.Objects.Widget#g:method:dragSourceSetIconName"), [dragSourceSetIconPixbuf]("GI.Gtk.Objects.Widget#g:method:dragSourceSetIconPixbuf"), [dragSourceSetIconStock]("GI.Gtk.Objects.Widget#g:method:dragSourceSetIconStock"), [dragSourceSetTargetList]("GI.Gtk.Objects.Widget#g:method:dragSourceSetTargetList"), [dragSourceUnset]("GI.Gtk.Objects.Widget#g:method:dragSourceUnset"), [dragUnhighlight]("GI.Gtk.Objects.Widget#g:method:dragUnhighlight"), [draw]("GI.Gtk.Objects.Widget#g:method:draw"), [ensureStyle]("GI.Gtk.Objects.Widget#g:method:ensureStyle"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [event]("GI.Gtk.Objects.Widget#g:method:event"), [forall]("GI.Gtk.Objects.Container#g:method:forall"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [foreach]("GI.Gtk.Objects.Container#g:method:foreach"), [freezeChildNotify]("GI.Gtk.Objects.Widget#g:method:freezeChildNotify"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabAdd]("GI.Gtk.Objects.Widget#g:method:grabAdd"), [grabDefault]("GI.Gtk.Objects.Widget#g:method:grabDefault"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [grabRemove]("GI.Gtk.Objects.Widget#g:method:grabRemove"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasGrab]("GI.Gtk.Objects.Widget#g:method:hasGrab"), [hasRcStyle]("GI.Gtk.Objects.Widget#g:method:hasRcStyle"), [hasScreen]("GI.Gtk.Objects.Widget#g:method:hasScreen"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [hideOnDelete]("GI.Gtk.Objects.Widget#g:method:hideOnDelete"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [inputShapeCombineRegion]("GI.Gtk.Objects.Widget#g:method:inputShapeCombineRegion"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [intersect]("GI.Gtk.Objects.Widget#g:method:intersect"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isComposited]("GI.Gtk.Objects.Widget#g:method:isComposited"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isToplevel]("GI.Gtk.Objects.Widget#g:method:isToplevel"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listAccelClosures]("GI.Gtk.Objects.Widget#g:method:listAccelClosures"), [listActionPrefixes]("GI.Gtk.Objects.Widget#g:method:listActionPrefixes"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [modifyBase]("GI.Gtk.Objects.Widget#g:method:modifyBase"), [modifyBg]("GI.Gtk.Objects.Widget#g:method:modifyBg"), [modifyCursor]("GI.Gtk.Objects.Widget#g:method:modifyCursor"), [modifyFg]("GI.Gtk.Objects.Widget#g:method:modifyFg"), [modifyFont]("GI.Gtk.Objects.Widget#g:method:modifyFont"), [modifyStyle]("GI.Gtk.Objects.Widget#g:method:modifyStyle"), [modifyText]("GI.Gtk.Objects.Widget#g:method:modifyText"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [overrideBackgroundColor]("GI.Gtk.Objects.Widget#g:method:overrideBackgroundColor"), [overrideColor]("GI.Gtk.Objects.Widget#g:method:overrideColor"), [overrideCursor]("GI.Gtk.Objects.Widget#g:method:overrideCursor"), [overrideFont]("GI.Gtk.Objects.Widget#g:method:overrideFont"), [overrideSymbolicColor]("GI.Gtk.Objects.Widget#g:method:overrideSymbolicColor"), [parserFinished]("GI.Gtk.Interfaces.Buildable#g:method:parserFinished"), [path]("GI.Gtk.Objects.Widget#g:method:path"), [propagateDraw]("GI.Gtk.Objects.Container#g:method:propagateDraw"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueComputeExpand]("GI.Gtk.Objects.Widget#g:method:queueComputeExpand"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueDrawArea]("GI.Gtk.Objects.Widget#g:method:queueDrawArea"), [queueDrawRegion]("GI.Gtk.Objects.Widget#g:method:queueDrawRegion"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [queueResizeNoRedraw]("GI.Gtk.Objects.Widget#g:method:queueResizeNoRedraw"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [regionIntersect]("GI.Gtk.Objects.Widget#g:method:regionIntersect"), [registerWindow]("GI.Gtk.Objects.Widget#g:method:registerWindow"), [remove]("GI.Gtk.Objects.Container#g:method:remove"), [removeAccelerator]("GI.Gtk.Objects.Widget#g:method:removeAccelerator"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [renderIcon]("GI.Gtk.Objects.Widget#g:method:renderIcon"), [renderIconPixbuf]("GI.Gtk.Objects.Widget#g:method:renderIconPixbuf"), [reparent]("GI.Gtk.Objects.Widget#g:method:reparent"), [resetRcStyles]("GI.Gtk.Objects.Widget#g:method:resetRcStyles"), [resetStyle]("GI.Gtk.Objects.Widget#g:method:resetStyle"), [resizeChildren]("GI.Gtk.Objects.Container#g:method:resizeChildren"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [sendExpose]("GI.Gtk.Objects.Widget#g:method:sendExpose"), [sendFocusChange]("GI.Gtk.Objects.Widget#g:method:sendFocusChange"), [shapeCombineRegion]("GI.Gtk.Objects.Widget#g:method:shapeCombineRegion"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [showAll]("GI.Gtk.Objects.Widget#g:method:showAll"), [showNow]("GI.Gtk.Objects.Widget#g:method:showNow"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [sizeAllocateWithBaseline]("GI.Gtk.Objects.Widget#g:method:sizeAllocateWithBaseline"), [sizeRequest]("GI.Gtk.Objects.Widget#g:method:sizeRequest"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [styleAttach]("GI.Gtk.Objects.Widget#g:method:styleAttach"), [styleGetProperty]("GI.Gtk.Objects.Widget#g:method:styleGetProperty"), [thawChildNotify]("GI.Gtk.Objects.Widget#g:method:thawChildNotify"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unregisterWindow]("GI.Gtk.Objects.Widget#g:method:unregisterWindow"), [unsetFocusChain]("GI.Gtk.Objects.Container#g:method:unsetFocusChain"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessible]("GI.Gtk.Objects.Widget#g:method:getAccessible"), [getActionGroup]("GI.Gtk.Objects.Widget#g:method:getActionGroup"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedSize]("GI.Gtk.Objects.Widget#g:method:getAllocatedSize"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getAppPaintable]("GI.Gtk.Objects.Widget#g:method:getAppPaintable"), [getBorderWidth]("GI.Gtk.Objects.Container#g:method:getBorderWidth"), [getCanDefault]("GI.Gtk.Objects.Widget#g:method:getCanDefault"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getChild]("GI.Gtk.Objects.Bin#g:method:getChild"), [getChildRequisition]("GI.Gtk.Objects.Widget#g:method:getChildRequisition"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getChildren]("GI.Gtk.Objects.Container#g:method:getChildren"), [getClip]("GI.Gtk.Objects.Widget#g:method:getClip"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCompositeName]("GI.Gtk.Objects.Widget#g:method:getCompositeName"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDeviceEnabled]("GI.Gtk.Objects.Widget#g:method:getDeviceEnabled"), [getDeviceEvents]("GI.Gtk.Objects.Widget#g:method:getDeviceEvents"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getDoubleBuffered]("GI.Gtk.Objects.Widget#g:method:getDoubleBuffered"), [getEvents]("GI.Gtk.Objects.Widget#g:method:getEvents"), [getFocusChain]("GI.Gtk.Objects.Container#g:method:getFocusChain"), [getFocusChild]("GI.Gtk.Objects.Container#g:method:getFocusChild"), [getFocusHadjustment]("GI.Gtk.Objects.Container#g:method:getFocusHadjustment"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusVadjustment]("GI.Gtk.Objects.Container#g:method:getFocusVadjustment"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHasWindow]("GI.Gtk.Objects.Widget#g:method:getHasWindow"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getIconName]("GI.Handy.Objects.PreferencesPage#g:method:getIconName"), [getInternalChild]("GI.Gtk.Interfaces.Buildable#g:method:getInternalChild"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginLeft]("GI.Gtk.Objects.Widget#g:method:getMarginLeft"), [getMarginRight]("GI.Gtk.Objects.Widget#g:method:getMarginRight"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getModifierMask]("GI.Gtk.Objects.Widget#g:method:getModifierMask"), [getModifierStyle]("GI.Gtk.Objects.Widget#g:method:getModifierStyle"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNoShowAll]("GI.Gtk.Objects.Widget#g:method:getNoShowAll"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getParentWindow]("GI.Gtk.Objects.Widget#g:method:getParentWindow"), [getPath]("GI.Gtk.Objects.Widget#g:method:getPath"), [getPathForChild]("GI.Gtk.Objects.Container#g:method:getPathForChild"), [getPointer]("GI.Gtk.Objects.Widget#g:method:getPointer"), [getPreferredHeight]("GI.Gtk.Objects.Widget#g:method:getPreferredHeight"), [getPreferredHeightAndBaselineForWidth]("GI.Gtk.Objects.Widget#g:method:getPreferredHeightAndBaselineForWidth"), [getPreferredHeightForWidth]("GI.Gtk.Objects.Widget#g:method:getPreferredHeightForWidth"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPreferredWidth]("GI.Gtk.Objects.Widget#g:method:getPreferredWidth"), [getPreferredWidthForHeight]("GI.Gtk.Objects.Widget#g:method:getPreferredWidthForHeight"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRequisition]("GI.Gtk.Objects.Widget#g:method:getRequisition"), [getResizeMode]("GI.Gtk.Objects.Container#g:method:getResizeMode"), [getRootWindow]("GI.Gtk.Objects.Widget#g:method:getRootWindow"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getScreen]("GI.Gtk.Objects.Widget#g:method:getScreen"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getState]("GI.Gtk.Objects.Widget#g:method:getState"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyle]("GI.Gtk.Objects.Widget#g:method:getStyle"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getSupportMultidevice]("GI.Gtk.Objects.Widget#g:method:getSupportMultidevice"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTitle]("GI.Handy.Objects.PreferencesPage#g:method:getTitle"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getTooltipWindow]("GI.Gtk.Objects.Widget#g:method:getTooltipWindow"), [getToplevel]("GI.Gtk.Objects.Widget#g:method:getToplevel"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getValignWithBaseline]("GI.Gtk.Objects.Widget#g:method:getValignWithBaseline"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getVisual]("GI.Gtk.Objects.Widget#g:method:getVisual"), [getWindow]("GI.Gtk.Objects.Widget#g:method:getWindow").
-- 
-- ==== Setters
-- [setAccelPath]("GI.Gtk.Objects.Widget#g:method:setAccelPath"), [setAllocation]("GI.Gtk.Objects.Widget#g:method:setAllocation"), [setAppPaintable]("GI.Gtk.Objects.Widget#g:method:setAppPaintable"), [setBorderWidth]("GI.Gtk.Objects.Container#g:method:setBorderWidth"), [setBuildableProperty]("GI.Gtk.Interfaces.Buildable#g:method:setBuildableProperty"), [setCanDefault]("GI.Gtk.Objects.Widget#g:method:setCanDefault"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setClip]("GI.Gtk.Objects.Widget#g:method:setClip"), [setCompositeName]("GI.Gtk.Objects.Widget#g:method:setCompositeName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDeviceEnabled]("GI.Gtk.Objects.Widget#g:method:setDeviceEnabled"), [setDeviceEvents]("GI.Gtk.Objects.Widget#g:method:setDeviceEvents"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setDoubleBuffered]("GI.Gtk.Objects.Widget#g:method:setDoubleBuffered"), [setEvents]("GI.Gtk.Objects.Widget#g:method:setEvents"), [setFocusChain]("GI.Gtk.Objects.Container#g:method:setFocusChain"), [setFocusChild]("GI.Gtk.Objects.Container#g:method:setFocusChild"), [setFocusHadjustment]("GI.Gtk.Objects.Container#g:method:setFocusHadjustment"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusVadjustment]("GI.Gtk.Objects.Container#g:method:setFocusVadjustment"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHasWindow]("GI.Gtk.Objects.Widget#g:method:setHasWindow"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setIconName]("GI.Handy.Objects.PreferencesPage#g:method:setIconName"), [setMapped]("GI.Gtk.Objects.Widget#g:method:setMapped"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginLeft]("GI.Gtk.Objects.Widget#g:method:setMarginLeft"), [setMarginRight]("GI.Gtk.Objects.Widget#g:method:setMarginRight"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setNoShowAll]("GI.Gtk.Objects.Widget#g:method:setNoShowAll"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setParentWindow]("GI.Gtk.Objects.Widget#g:method:setParentWindow"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRealized]("GI.Gtk.Objects.Widget#g:method:setRealized"), [setReallocateRedraws]("GI.Gtk.Objects.Container#g:method:setReallocateRedraws"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setRedrawOnAllocate]("GI.Gtk.Objects.Widget#g:method:setRedrawOnAllocate"), [setResizeMode]("GI.Gtk.Objects.Container#g:method:setResizeMode"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setState]("GI.Gtk.Objects.Widget#g:method:setState"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setStyle]("GI.Gtk.Objects.Widget#g:method:setStyle"), [setSupportMultidevice]("GI.Gtk.Objects.Widget#g:method:setSupportMultidevice"), [setTitle]("GI.Handy.Objects.PreferencesPage#g:method:setTitle"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setTooltipWindow]("GI.Gtk.Objects.Widget#g:method:setTooltipWindow"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible"), [setVisual]("GI.Gtk.Objects.Widget#g:method:setVisual"), [setWindow]("GI.Gtk.Objects.Widget#g:method:setWindow").

#if defined(ENABLE_OVERLOADING)
    ResolvePreferencesPageMethod            ,
#endif

-- ** getIconName #method:getIconName#

#if defined(ENABLE_OVERLOADING)
    PreferencesPageGetIconNameMethodInfo    ,
#endif
    preferencesPageGetIconName              ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    PreferencesPageGetTitleMethodInfo       ,
#endif
    preferencesPageGetTitle                 ,


-- ** new #method:new#

    preferencesPageNew                      ,


-- ** setIconName #method:setIconName#

#if defined(ENABLE_OVERLOADING)
    PreferencesPageSetIconNameMethodInfo    ,
#endif
    preferencesPageSetIconName              ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    PreferencesPageSetTitleMethodInfo       ,
#endif
    preferencesPageSetTitle                 ,




 -- * Properties


-- ** iconName #attr:iconName#
-- | The icon name for this page of preferences.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    PreferencesPageIconNamePropertyInfo     ,
#endif
    clearPreferencesPageIconName            ,
    constructPreferencesPageIconName        ,
    getPreferencesPageIconName              ,
#if defined(ENABLE_OVERLOADING)
    preferencesPageIconName                 ,
#endif
    setPreferencesPageIconName              ,


-- ** title #attr:title#
-- | The title for this page of preferences.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    PreferencesPageTitlePropertyInfo        ,
#endif
    clearPreferencesPageTitle               ,
    constructPreferencesPageTitle           ,
    getPreferencesPageTitle                 ,
#if defined(ENABLE_OVERLOADING)
    preferencesPageTitle                    ,
#endif
    setPreferencesPageTitle                 ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Bin as Gtk.Bin
import qualified GI.Gtk.Objects.Container as Gtk.Container
import qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "hdy_preferences_page_get_type"
    c_hdy_preferences_page_get_type :: IO B.Types.GType

instance B.Types.TypedObject PreferencesPage where
    glibType :: IO GType
glibType = IO GType
c_hdy_preferences_page_get_type

instance B.Types.GObject PreferencesPage

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

instance O.HasParentTypes PreferencesPage
type instance O.ParentTypes PreferencesPage = '[Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolvePreferencesPageMethod (t :: Symbol) (o :: *) :: * where
    ResolvePreferencesPageMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolvePreferencesPageMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolvePreferencesPageMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolvePreferencesPageMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolvePreferencesPageMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
    ResolvePreferencesPageMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
    ResolvePreferencesPageMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolvePreferencesPageMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolvePreferencesPageMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePreferencesPageMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePreferencesPageMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolvePreferencesPageMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
    ResolvePreferencesPageMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolvePreferencesPageMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
    ResolvePreferencesPageMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
    ResolvePreferencesPageMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
    ResolvePreferencesPageMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
    ResolvePreferencesPageMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    ResolvePreferencesPageMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
    ResolvePreferencesPageMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolvePreferencesPageMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolvePreferencesPageMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolvePreferencesPageMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolvePreferencesPageMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolvePreferencesPageMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolvePreferencesPageMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolvePreferencesPageMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolvePreferencesPageMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolvePreferencesPageMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolvePreferencesPageMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolvePreferencesPageMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
    ResolvePreferencesPageMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolvePreferencesPageMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolvePreferencesPageMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolvePreferencesPageMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolvePreferencesPageMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolvePreferencesPageMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolvePreferencesPageMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolvePreferencesPageMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolvePreferencesPageMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
    ResolvePreferencesPageMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolvePreferencesPageMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolvePreferencesPageMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolvePreferencesPageMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolvePreferencesPageMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolvePreferencesPageMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolvePreferencesPageMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolvePreferencesPageMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolvePreferencesPageMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolvePreferencesPageMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolvePreferencesPageMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolvePreferencesPageMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolvePreferencesPageMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
    ResolvePreferencesPageMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
    ResolvePreferencesPageMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolvePreferencesPageMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolvePreferencesPageMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolvePreferencesPageMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
    ResolvePreferencesPageMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
    ResolvePreferencesPageMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolvePreferencesPageMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolvePreferencesPageMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolvePreferencesPageMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePreferencesPageMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolvePreferencesPageMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
    ResolvePreferencesPageMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePreferencesPageMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePreferencesPageMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolvePreferencesPageMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
    ResolvePreferencesPageMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolvePreferencesPageMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolvePreferencesPageMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolvePreferencesPageMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolvePreferencesPageMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolvePreferencesPageMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
    ResolvePreferencesPageMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
    ResolvePreferencesPageMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolvePreferencesPageMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolvePreferencesPageMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
    ResolvePreferencesPageMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolvePreferencesPageMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolvePreferencesPageMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolvePreferencesPageMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolvePreferencesPageMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
    ResolvePreferencesPageMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolvePreferencesPageMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
    ResolvePreferencesPageMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolvePreferencesPageMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePreferencesPageMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolvePreferencesPageMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolvePreferencesPageMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolvePreferencesPageMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolvePreferencesPageMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolvePreferencesPageMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolvePreferencesPageMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolvePreferencesPageMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolvePreferencesPageMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolvePreferencesPageMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolvePreferencesPageMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
    ResolvePreferencesPageMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
    ResolvePreferencesPageMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
    ResolvePreferencesPageMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
    ResolvePreferencesPageMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
    ResolvePreferencesPageMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
    ResolvePreferencesPageMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
    ResolvePreferencesPageMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePreferencesPageMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePreferencesPageMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
    ResolvePreferencesPageMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
    ResolvePreferencesPageMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
    ResolvePreferencesPageMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
    ResolvePreferencesPageMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
    ResolvePreferencesPageMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolvePreferencesPageMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
    ResolvePreferencesPageMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
    ResolvePreferencesPageMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolvePreferencesPageMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolvePreferencesPageMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolvePreferencesPageMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
    ResolvePreferencesPageMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
    ResolvePreferencesPageMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolvePreferencesPageMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolvePreferencesPageMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolvePreferencesPageMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePreferencesPageMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePreferencesPageMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
    ResolvePreferencesPageMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
    ResolvePreferencesPageMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolvePreferencesPageMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolvePreferencesPageMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolvePreferencesPageMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolvePreferencesPageMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
    ResolvePreferencesPageMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
    ResolvePreferencesPageMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
    ResolvePreferencesPageMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
    ResolvePreferencesPageMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolvePreferencesPageMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
    ResolvePreferencesPageMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePreferencesPageMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
    ResolvePreferencesPageMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
    ResolvePreferencesPageMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
    ResolvePreferencesPageMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolvePreferencesPageMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
    ResolvePreferencesPageMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
    ResolvePreferencesPageMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolvePreferencesPageMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
    ResolvePreferencesPageMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
    ResolvePreferencesPageMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePreferencesPageMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePreferencesPageMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
    ResolvePreferencesPageMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
    ResolvePreferencesPageMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
    ResolvePreferencesPageMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePreferencesPageMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolvePreferencesPageMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolvePreferencesPageMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolvePreferencesPageMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolvePreferencesPageMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolvePreferencesPageMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePreferencesPageMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
    ResolvePreferencesPageMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
    ResolvePreferencesPageMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolvePreferencesPageMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePreferencesPageMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolvePreferencesPageMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolvePreferencesPageMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolvePreferencesPageMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolvePreferencesPageMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
    ResolvePreferencesPageMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolvePreferencesPageMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolvePreferencesPageMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolvePreferencesPageMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
    ResolvePreferencesPageMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
    ResolvePreferencesPageMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
    ResolvePreferencesPageMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolvePreferencesPageMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
    ResolvePreferencesPageMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
    ResolvePreferencesPageMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolvePreferencesPageMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolvePreferencesPageMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
    ResolvePreferencesPageMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolvePreferencesPageMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
    ResolvePreferencesPageMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePreferencesPageMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
    ResolvePreferencesPageMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
    ResolvePreferencesPageMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolvePreferencesPageMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolvePreferencesPageMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
    ResolvePreferencesPageMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
    ResolvePreferencesPageMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
    ResolvePreferencesPageMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
    ResolvePreferencesPageMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolvePreferencesPageMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolvePreferencesPageMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    ResolvePreferencesPageMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolvePreferencesPageMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolvePreferencesPageMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolvePreferencesPageMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolvePreferencesPageMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolvePreferencesPageMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
    ResolvePreferencesPageMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolvePreferencesPageMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolvePreferencesPageMethod "getIconName" o = PreferencesPageGetIconNameMethodInfo
    ResolvePreferencesPageMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolvePreferencesPageMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolvePreferencesPageMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolvePreferencesPageMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolvePreferencesPageMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
    ResolvePreferencesPageMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
    ResolvePreferencesPageMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolvePreferencesPageMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolvePreferencesPageMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolvePreferencesPageMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
    ResolvePreferencesPageMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolvePreferencesPageMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
    ResolvePreferencesPageMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolvePreferencesPageMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolvePreferencesPageMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolvePreferencesPageMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
    ResolvePreferencesPageMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolvePreferencesPageMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    ResolvePreferencesPageMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
    ResolvePreferencesPageMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
    ResolvePreferencesPageMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
    ResolvePreferencesPageMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
    ResolvePreferencesPageMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolvePreferencesPageMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
    ResolvePreferencesPageMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
    ResolvePreferencesPageMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePreferencesPageMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePreferencesPageMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolvePreferencesPageMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolvePreferencesPageMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolvePreferencesPageMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
    ResolvePreferencesPageMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
    ResolvePreferencesPageMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
    ResolvePreferencesPageMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolvePreferencesPageMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
    ResolvePreferencesPageMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolvePreferencesPageMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolvePreferencesPageMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolvePreferencesPageMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
    ResolvePreferencesPageMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolvePreferencesPageMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
    ResolvePreferencesPageMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolvePreferencesPageMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolvePreferencesPageMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolvePreferencesPageMethod "getTitle" o = PreferencesPageGetTitleMethodInfo
    ResolvePreferencesPageMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolvePreferencesPageMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolvePreferencesPageMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolvePreferencesPageMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolvePreferencesPageMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolvePreferencesPageMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
    ResolvePreferencesPageMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolvePreferencesPageMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolvePreferencesPageMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolvePreferencesPageMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
    ResolvePreferencesPageMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
    ResolvePreferencesPageMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolvePreferencesPageMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
    ResolvePreferencesPageMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
    ResolvePreferencesPageMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
    ResolvePreferencesPageMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolvePreferencesPageMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
    ResolvePreferencesPageMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolvePreferencesPageMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolvePreferencesPageMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
    ResolvePreferencesPageMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
    ResolvePreferencesPageMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePreferencesPageMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePreferencesPageMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
    ResolvePreferencesPageMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
    ResolvePreferencesPageMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolvePreferencesPageMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
    ResolvePreferencesPageMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
    ResolvePreferencesPageMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
    ResolvePreferencesPageMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
    ResolvePreferencesPageMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolvePreferencesPageMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolvePreferencesPageMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolvePreferencesPageMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolvePreferencesPageMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolvePreferencesPageMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolvePreferencesPageMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolvePreferencesPageMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
    ResolvePreferencesPageMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolvePreferencesPageMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolvePreferencesPageMethod "setIconName" o = PreferencesPageSetIconNameMethodInfo
    ResolvePreferencesPageMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
    ResolvePreferencesPageMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolvePreferencesPageMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolvePreferencesPageMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
    ResolvePreferencesPageMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
    ResolvePreferencesPageMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolvePreferencesPageMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolvePreferencesPageMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolvePreferencesPageMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
    ResolvePreferencesPageMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolvePreferencesPageMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolvePreferencesPageMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
    ResolvePreferencesPageMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePreferencesPageMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
    ResolvePreferencesPageMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
    ResolvePreferencesPageMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolvePreferencesPageMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
    ResolvePreferencesPageMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
    ResolvePreferencesPageMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolvePreferencesPageMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolvePreferencesPageMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
    ResolvePreferencesPageMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolvePreferencesPageMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
    ResolvePreferencesPageMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolvePreferencesPageMethod "setTitle" o = PreferencesPageSetTitleMethodInfo
    ResolvePreferencesPageMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolvePreferencesPageMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolvePreferencesPageMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolvePreferencesPageMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolvePreferencesPageMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolvePreferencesPageMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolvePreferencesPageMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolvePreferencesPageMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
    ResolvePreferencesPageMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
    ResolvePreferencesPageMethod l o = O.MethodResolutionFailed l o

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

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

#endif

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

#endif

-- VVV Prop "icon-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

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

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

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

-- | Set the value of the “@icon-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' #iconName
-- @
clearPreferencesPageIconName :: (MonadIO m, IsPreferencesPage o) => o -> m ()
clearPreferencesPageIconName :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesPage o) =>
o -> m ()
clearPreferencesPageIconName o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"icon-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data PreferencesPageIconNamePropertyInfo
instance AttrInfo PreferencesPageIconNamePropertyInfo where
    type AttrAllowedOps PreferencesPageIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PreferencesPageIconNamePropertyInfo = IsPreferencesPage
    type AttrSetTypeConstraint PreferencesPageIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PreferencesPageIconNamePropertyInfo = (~) T.Text
    type AttrTransferType PreferencesPageIconNamePropertyInfo = T.Text
    type AttrGetType PreferencesPageIconNamePropertyInfo = (Maybe T.Text)
    type AttrLabel PreferencesPageIconNamePropertyInfo = "icon-name"
    type AttrOrigin PreferencesPageIconNamePropertyInfo = PreferencesPage
    attrGet = getPreferencesPageIconName
    attrSet = setPreferencesPageIconName
    attrTransfer _ v = do
        return v
    attrConstruct = constructPreferencesPageIconName
    attrClear = clearPreferencesPageIconName
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.PreferencesPage.iconName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.2/docs/GI-Handy-Objects-PreferencesPage.html#g:attr:iconName"
        })
#endif

-- VVV Prop "title"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

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

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

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

-- | Set the value of the “@title@” 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' #title
-- @
clearPreferencesPageTitle :: (MonadIO m, IsPreferencesPage o) => o -> m ()
clearPreferencesPageTitle :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesPage o) =>
o -> m ()
clearPreferencesPageTitle o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"title" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data PreferencesPageTitlePropertyInfo
instance AttrInfo PreferencesPageTitlePropertyInfo where
    type AttrAllowedOps PreferencesPageTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PreferencesPageTitlePropertyInfo = IsPreferencesPage
    type AttrSetTypeConstraint PreferencesPageTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PreferencesPageTitlePropertyInfo = (~) T.Text
    type AttrTransferType PreferencesPageTitlePropertyInfo = T.Text
    type AttrGetType PreferencesPageTitlePropertyInfo = (Maybe T.Text)
    type AttrLabel PreferencesPageTitlePropertyInfo = "title"
    type AttrOrigin PreferencesPageTitlePropertyInfo = PreferencesPage
    attrGet = getPreferencesPageTitle
    attrSet = setPreferencesPageTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructPreferencesPageTitle
    attrClear = clearPreferencesPageTitle
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.PreferencesPage.title"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.2/docs/GI-Handy-Objects-PreferencesPage.html#g:attr:title"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PreferencesPage
type instance O.AttributeList PreferencesPage = PreferencesPageAttributeList
type PreferencesPageAttributeList = ('[ '("appPaintable", Gtk.Widget.WidgetAppPaintablePropertyInfo), '("borderWidth", Gtk.Container.ContainerBorderWidthPropertyInfo), '("canDefault", Gtk.Widget.WidgetCanDefaultPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("child", Gtk.Container.ContainerChildPropertyInfo), '("compositeChild", Gtk.Widget.WidgetCompositeChildPropertyInfo), '("doubleBuffered", Gtk.Widget.WidgetDoubleBufferedPropertyInfo), '("events", Gtk.Widget.WidgetEventsPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("iconName", PreferencesPageIconNamePropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginLeft", Gtk.Widget.WidgetMarginLeftPropertyInfo), '("marginRight", Gtk.Widget.WidgetMarginRightPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("noShowAll", Gtk.Widget.WidgetNoShowAllPropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("title", PreferencesPageTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
preferencesPageIconName :: AttrLabelProxy "iconName"
preferencesPageIconName = AttrLabelProxy

preferencesPageTitle :: AttrLabelProxy "title"
preferencesPageTitle = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PreferencesPage = PreferencesPageSignalList
type PreferencesPageSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("compositedChanged", Gtk.Widget.WidgetCompositedChangedSignalInfo), '("configureEvent", Gtk.Widget.WidgetConfigureEventSignalInfo), '("damageEvent", Gtk.Widget.WidgetDamageEventSignalInfo), '("deleteEvent", Gtk.Widget.WidgetDeleteEventSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("destroyEvent", Gtk.Widget.WidgetDestroyEventSignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("draw", Gtk.Widget.WidgetDrawSignalInfo), '("enterNotifyEvent", Gtk.Widget.WidgetEnterNotifyEventSignalInfo), '("event", Gtk.Widget.WidgetEventSignalInfo), '("eventAfter", Gtk.Widget.WidgetEventAfterSignalInfo), '("focus", Gtk.Widget.WidgetFocusSignalInfo), '("focusInEvent", Gtk.Widget.WidgetFocusInEventSignalInfo), '("focusOutEvent", Gtk.Widget.WidgetFocusOutEventSignalInfo), '("grabBrokenEvent", Gtk.Widget.WidgetGrabBrokenEventSignalInfo), '("grabFocus", Gtk.Widget.WidgetGrabFocusSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("hierarchyChanged", Gtk.Widget.WidgetHierarchyChangedSignalInfo), '("keyPressEvent", Gtk.Widget.WidgetKeyPressEventSignalInfo), '("keyReleaseEvent", Gtk.Widget.WidgetKeyReleaseEventSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("leaveNotifyEvent", Gtk.Widget.WidgetLeaveNotifyEventSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mapEvent", Gtk.Widget.WidgetMapEventSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("motionNotifyEvent", Gtk.Widget.WidgetMotionNotifyEventSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("parentSet", Gtk.Widget.WidgetParentSetSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("screenChanged", Gtk.Widget.WidgetScreenChangedSignalInfo), '("scrollEvent", Gtk.Widget.WidgetScrollEventSignalInfo), '("selectionClearEvent", Gtk.Widget.WidgetSelectionClearEventSignalInfo), '("selectionGet", Gtk.Widget.WidgetSelectionGetSignalInfo), '("selectionNotifyEvent", Gtk.Widget.WidgetSelectionNotifyEventSignalInfo), '("selectionReceived", Gtk.Widget.WidgetSelectionReceivedSignalInfo), '("selectionRequestEvent", Gtk.Widget.WidgetSelectionRequestEventSignalInfo), '("setFocusChild", Gtk.Container.ContainerSetFocusChildSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("showHelp", Gtk.Widget.WidgetShowHelpSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateChanged", Gtk.Widget.WidgetStateChangedSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleSet", Gtk.Widget.WidgetStyleSetSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("touchEvent", Gtk.Widget.WidgetTouchEventSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unmapEvent", Gtk.Widget.WidgetUnmapEventSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, *)])

#endif

-- method PreferencesPage::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Handy" , name = "PreferencesPage" })
-- throws : False
-- Skip return : False

foreign import ccall "hdy_preferences_page_new" hdy_preferences_page_new :: 
    IO (Ptr PreferencesPage)

-- | Creates a new @HdyPreferencesPage@.
-- 
-- /Since: 1.0/
preferencesPageNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m PreferencesPage
    -- ^ __Returns:__ the newly created @HdyPreferencesPage@
preferencesPageNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m PreferencesPage
preferencesPageNew  = IO PreferencesPage -> m PreferencesPage
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PreferencesPage -> m PreferencesPage)
-> IO PreferencesPage -> m PreferencesPage
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesPage
result <- IO (Ptr PreferencesPage)
hdy_preferences_page_new
    Text -> Ptr PreferencesPage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"preferencesPageNew" Ptr PreferencesPage
result
    PreferencesPage
result' <- ((ManagedPtr PreferencesPage -> PreferencesPage)
-> Ptr PreferencesPage -> IO PreferencesPage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PreferencesPage -> PreferencesPage
PreferencesPage) Ptr PreferencesPage
result
    PreferencesPage -> IO PreferencesPage
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PreferencesPage
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PreferencesPage::get_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "PreferencesPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a preferences page" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "hdy_preferences_page_get_icon_name" hdy_preferences_page_get_icon_name :: 
    Ptr PreferencesPage ->                  -- self : TInterface (Name {namespace = "Handy", name = "PreferencesPage"})
    IO CString

-- | Gets the icon name for /@self@/.
-- 
-- /Since: 1.0/
preferencesPageGetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesPage a) =>
    a
    -- ^ /@self@/: a preferences page
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the icon name for /@self@/
preferencesPageGetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesPage a) =>
a -> m (Maybe Text)
preferencesPageGetIconName a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr PreferencesPage
self' <- a -> IO (Ptr PreferencesPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr PreferencesPage -> IO CString
hdy_preferences_page_get_icon_name Ptr PreferencesPage
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data PreferencesPageGetIconNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsPreferencesPage a) => O.OverloadedMethod PreferencesPageGetIconNameMethodInfo a signature where
    overloadedMethod = preferencesPageGetIconName

instance O.OverloadedMethodInfo PreferencesPageGetIconNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.PreferencesPage.preferencesPageGetIconName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.2/docs/GI-Handy-Objects-PreferencesPage.html#v:preferencesPageGetIconName"
        })


#endif

-- method PreferencesPage::get_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "PreferencesPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a preferences page" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "hdy_preferences_page_get_title" hdy_preferences_page_get_title :: 
    Ptr PreferencesPage ->                  -- self : TInterface (Name {namespace = "Handy", name = "PreferencesPage"})
    IO CString

-- | Gets the title of /@self@/.
-- 
-- /Since: 1.0/
preferencesPageGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesPage a) =>
    a
    -- ^ /@self@/: a preferences page
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the title of the /@self@/
preferencesPageGetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesPage a) =>
a -> m (Maybe Text)
preferencesPageGetTitle a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr PreferencesPage
self' <- a -> IO (Ptr PreferencesPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr PreferencesPage -> IO CString
hdy_preferences_page_get_title Ptr PreferencesPage
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data PreferencesPageGetTitleMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsPreferencesPage a) => O.OverloadedMethod PreferencesPageGetTitleMethodInfo a signature where
    overloadedMethod = preferencesPageGetTitle

instance O.OverloadedMethodInfo PreferencesPageGetTitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.PreferencesPage.preferencesPageGetTitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.2/docs/GI-Handy-Objects-PreferencesPage.html#v:preferencesPageGetTitle"
        })


#endif

-- method PreferencesPage::set_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "PreferencesPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a preferences page" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the icon name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_preferences_page_set_icon_name" hdy_preferences_page_set_icon_name :: 
    Ptr PreferencesPage ->                  -- self : TInterface (Name {namespace = "Handy", name = "PreferencesPage"})
    CString ->                              -- icon_name : TBasicType TUTF8
    IO ()

-- | Sets the icon name for /@self@/.
-- 
-- /Since: 1.0/
preferencesPageSetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesPage a) =>
    a
    -- ^ /@self@/: a preferences page
    -> Maybe (T.Text)
    -- ^ /@iconName@/: the icon name
    -> m ()
preferencesPageSetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesPage a) =>
a -> Maybe Text -> m ()
preferencesPageSetIconName a
self Maybe Text
iconName = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesPage
self' <- a -> IO (Ptr PreferencesPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
maybeIconName <- case Maybe Text
iconName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jIconName -> do
            CString
jIconName' <- Text -> IO CString
textToCString Text
jIconName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jIconName'
    Ptr PreferencesPage -> CString -> IO ()
hdy_preferences_page_set_icon_name Ptr PreferencesPage
self' CString
maybeIconName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeIconName
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PreferencesPageSetIconNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsPreferencesPage a) => O.OverloadedMethod PreferencesPageSetIconNameMethodInfo a signature where
    overloadedMethod = preferencesPageSetIconName

instance O.OverloadedMethodInfo PreferencesPageSetIconNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.PreferencesPage.preferencesPageSetIconName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.2/docs/GI-Handy-Objects-PreferencesPage.html#v:preferencesPageSetIconName"
        })


#endif

-- method PreferencesPage::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "PreferencesPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a preferences page" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the title of the page"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_preferences_page_set_title" hdy_preferences_page_set_title :: 
    Ptr PreferencesPage ->                  -- self : TInterface (Name {namespace = "Handy", name = "PreferencesPage"})
    CString ->                              -- title : TBasicType TUTF8
    IO ()

-- | Sets the title of /@self@/.
-- 
-- /Since: 1.0/
preferencesPageSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesPage a) =>
    a
    -- ^ /@self@/: a preferences page
    -> Maybe (T.Text)
    -- ^ /@title@/: the title of the page
    -> m ()
preferencesPageSetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesPage a) =>
a -> Maybe Text -> m ()
preferencesPageSetTitle a
self Maybe Text
title = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesPage
self' <- a -> IO (Ptr PreferencesPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
maybeTitle <- case Maybe Text
title of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jTitle -> do
            CString
jTitle' <- Text -> IO CString
textToCString Text
jTitle
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jTitle'
    Ptr PreferencesPage -> CString -> IO ()
hdy_preferences_page_set_title Ptr PreferencesPage
self' CString
maybeTitle
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeTitle
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PreferencesPageSetTitleMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsPreferencesPage a) => O.OverloadedMethod PreferencesPageSetTitleMethodInfo a signature where
    overloadedMethod = preferencesPageSetTitle

instance O.OverloadedMethodInfo PreferencesPageSetTitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.PreferencesPage.preferencesPageSetTitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.2/docs/GI-Handy-Objects-PreferencesPage.html#v:preferencesPageSetTitle"
        })


#endif