{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Handy.Objects.PreferencesRow
    ( 

-- * Exported types
    PreferencesRow(..)                      ,
    IsPreferencesRow                        ,
    toPreferencesRow                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolvePreferencesRowMethod             ,
#endif


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    PreferencesRowGetTitleMethodInfo        ,
#endif
    preferencesRowGetTitle                  ,


-- ** getUseUnderline #method:getUseUnderline#

#if defined(ENABLE_OVERLOADING)
    PreferencesRowGetUseUnderlineMethodInfo ,
#endif
    preferencesRowGetUseUnderline           ,


-- ** new #method:new#

    preferencesRowNew                       ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    PreferencesRowSetTitleMethodInfo        ,
#endif
    preferencesRowSetTitle                  ,


-- ** setUseUnderline #method:setUseUnderline#

#if defined(ENABLE_OVERLOADING)
    PreferencesRowSetUseUnderlineMethodInfo ,
#endif
    preferencesRowSetUseUnderline           ,




 -- * Properties
-- ** title #attr:title#
-- | The title of the preference represented by this row.
-- 
-- /Since: 0.0.10/

#if defined(ENABLE_OVERLOADING)
    PreferencesRowTitlePropertyInfo         ,
#endif
    clearPreferencesRowTitle                ,
    constructPreferencesRowTitle            ,
    getPreferencesRowTitle                  ,
#if defined(ENABLE_OVERLOADING)
    preferencesRowTitle                     ,
#endif
    setPreferencesRowTitle                  ,


-- ** useUnderline #attr:useUnderline#
-- | Whether an embedded underline in the text of the title indicates a
-- mnemonic.
-- 
-- /Since: 0.0.10/

#if defined(ENABLE_OVERLOADING)
    PreferencesRowUseUnderlinePropertyInfo  ,
#endif
    constructPreferencesRowUseUnderline     ,
    getPreferencesRowUseUnderline           ,
#if defined(ENABLE_OVERLOADING)
    preferencesRowUseUnderline              ,
#endif
    setPreferencesRowUseUnderline           ,




    ) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Actionable as Gtk.Actionable
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.ListBoxRow as Gtk.ListBoxRow
import qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "hdy_preferences_row_get_type"
    c_hdy_preferences_row_get_type :: IO B.Types.GType

instance B.Types.TypedObject PreferencesRow where
    glibType :: IO GType
glibType = IO GType
c_hdy_preferences_row_get_type

instance B.Types.GObject PreferencesRow

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

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

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

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

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

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

#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' preferencesRow #title
-- @
getPreferencesRowTitle :: (MonadIO m, IsPreferencesRow o) => o -> m (Maybe T.Text)
getPreferencesRowTitle :: o -> m (Maybe Text)
getPreferencesRowTitle o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj 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' preferencesRow [ #title 'Data.GI.Base.Attributes.:=' value ]
-- @
setPreferencesRowTitle :: (MonadIO m, IsPreferencesRow o) => o -> T.Text -> m ()
setPreferencesRowTitle :: o -> Text -> m ()
setPreferencesRowTitle o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj 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`.
constructPreferencesRowTitle :: (IsPreferencesRow o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPreferencesRowTitle :: Text -> m (GValueConstruct o)
constructPreferencesRowTitle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
-- @
clearPreferencesRowTitle :: (MonadIO m, IsPreferencesRow o) => o -> m ()
clearPreferencesRowTitle :: o -> m ()
clearPreferencesRowTitle o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"title" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data PreferencesRowTitlePropertyInfo
instance AttrInfo PreferencesRowTitlePropertyInfo where
    type AttrAllowedOps PreferencesRowTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PreferencesRowTitlePropertyInfo = IsPreferencesRow
    type AttrSetTypeConstraint PreferencesRowTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PreferencesRowTitlePropertyInfo = (~) T.Text
    type AttrTransferType PreferencesRowTitlePropertyInfo = T.Text
    type AttrGetType PreferencesRowTitlePropertyInfo = (Maybe T.Text)
    type AttrLabel PreferencesRowTitlePropertyInfo = "title"
    type AttrOrigin PreferencesRowTitlePropertyInfo = PreferencesRow
    attrGet = getPreferencesRowTitle
    attrSet = setPreferencesRowTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructPreferencesRowTitle
    attrClear = clearPreferencesRowTitle
#endif

-- VVV Prop "use-underline"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

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

-- | Construct a `GValueConstruct` with valid value for the “@use-underline@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPreferencesRowUseUnderline :: (IsPreferencesRow o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPreferencesRowUseUnderline :: Bool -> m (GValueConstruct o)
constructPreferencesRowUseUnderline Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-underline" Bool
val

#if defined(ENABLE_OVERLOADING)
data PreferencesRowUseUnderlinePropertyInfo
instance AttrInfo PreferencesRowUseUnderlinePropertyInfo where
    type AttrAllowedOps PreferencesRowUseUnderlinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PreferencesRowUseUnderlinePropertyInfo = IsPreferencesRow
    type AttrSetTypeConstraint PreferencesRowUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PreferencesRowUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferType PreferencesRowUseUnderlinePropertyInfo = Bool
    type AttrGetType PreferencesRowUseUnderlinePropertyInfo = Bool
    type AttrLabel PreferencesRowUseUnderlinePropertyInfo = "use-underline"
    type AttrOrigin PreferencesRowUseUnderlinePropertyInfo = PreferencesRow
    attrGet = getPreferencesRowUseUnderline
    attrSet = setPreferencesRowUseUnderline
    attrTransfer _ v = do
        return v
    attrConstruct = constructPreferencesRowUseUnderline
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PreferencesRow
type instance O.AttributeList PreferencesRow = PreferencesRowAttributeList
type PreferencesRowAttributeList = ('[ '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("activatable", Gtk.ListBoxRow.ListBoxRowActivatablePropertyInfo), '("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), '("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), '("selectable", Gtk.ListBoxRow.ListBoxRowSelectablePropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("title", PreferencesRowTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useUnderline", PreferencesRowUseUnderlinePropertyInfo), '("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)
preferencesRowTitle :: AttrLabelProxy "title"
preferencesRowTitle = AttrLabelProxy

preferencesRowUseUnderline :: AttrLabelProxy "useUnderline"
preferencesRowUseUnderline = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PreferencesRow = PreferencesRowSignalList
type PreferencesRowSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("activate", Gtk.ListBoxRow.ListBoxRowActivateSignalInfo), '("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 PreferencesRow::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Handy" , name = "PreferencesRow" })
-- throws : False
-- Skip return : False

foreign import ccall "hdy_preferences_row_new" hdy_preferences_row_new :: 
    IO (Ptr PreferencesRow)

-- | Creates a new t'GI.Handy.Objects.PreferencesRow.PreferencesRow'.
-- 
-- /Since: 0.0.10/
preferencesRowNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m PreferencesRow
    -- ^ __Returns:__ a new t'GI.Handy.Objects.PreferencesRow.PreferencesRow'
preferencesRowNew :: m PreferencesRow
preferencesRowNew  = IO PreferencesRow -> m PreferencesRow
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PreferencesRow -> m PreferencesRow)
-> IO PreferencesRow -> m PreferencesRow
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesRow
result <- IO (Ptr PreferencesRow)
hdy_preferences_row_new
    Text -> Ptr PreferencesRow -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"preferencesRowNew" Ptr PreferencesRow
result
    PreferencesRow
result' <- ((ManagedPtr PreferencesRow -> PreferencesRow)
-> Ptr PreferencesRow -> IO PreferencesRow
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PreferencesRow -> PreferencesRow
PreferencesRow) Ptr PreferencesRow
result
    PreferencesRow -> IO PreferencesRow
forall (m :: * -> *) a. Monad m => a -> m a
return PreferencesRow
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PreferencesRow::get_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "PreferencesRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #HdyPreferencesRow"
--                 , 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_row_get_title" hdy_preferences_row_get_title :: 
    Ptr PreferencesRow ->                   -- self : TInterface (Name {namespace = "Handy", name = "PreferencesRow"})
    IO CString

-- | Gets the title of the preference represented by /@self@/.
-- 
-- /Since: 0.0.10/
preferencesRowGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesRow a) =>
    a
    -- ^ /@self@/: a t'GI.Handy.Objects.PreferencesRow.PreferencesRow'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the title of the preference represented
    --          by /@self@/, or 'P.Nothing'.
preferencesRowGetTitle :: a -> m (Maybe Text)
preferencesRowGetTitle a
self = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesRow
self' <- a -> IO (Ptr PreferencesRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr PreferencesRow -> IO CString
hdy_preferences_row_get_title Ptr PreferencesRow
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 (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 (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data PreferencesRowGetTitleMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsPreferencesRow a) => O.MethodInfo PreferencesRowGetTitleMethodInfo a signature where
    overloadedMethod = preferencesRowGetTitle

#endif

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

foreign import ccall "hdy_preferences_row_get_use_underline" hdy_preferences_row_get_use_underline :: 
    Ptr PreferencesRow ->                   -- self : TInterface (Name {namespace = "Handy", name = "PreferencesRow"})
    IO CInt

-- | Gets whether an embedded underline in the text of the title indicates a
-- mnemonic. See 'GI.Handy.Objects.PreferencesRow.preferencesRowSetUseUnderline'.
-- 
-- /Since: 0.0.10/
preferencesRowGetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesRow a) =>
    a
    -- ^ /@self@/: a t'GI.Handy.Objects.PreferencesRow.PreferencesRow'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if an embedded underline in the title indicates the mnemonic
    --          accelerator keys.
preferencesRowGetUseUnderline :: a -> m Bool
preferencesRowGetUseUnderline a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesRow
self' <- a -> IO (Ptr PreferencesRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr PreferencesRow -> IO CInt
hdy_preferences_row_get_use_underline Ptr PreferencesRow
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PreferencesRowGetUseUnderlineMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPreferencesRow a) => O.MethodInfo PreferencesRowGetUseUnderlineMethodInfo a signature where
    overloadedMethod = preferencesRowGetUseUnderline

#endif

-- method PreferencesRow::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "PreferencesRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #HdyPreferencesRow"
--                 , 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, or %NULL."
--                 , 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_row_set_title" hdy_preferences_row_set_title :: 
    Ptr PreferencesRow ->                   -- self : TInterface (Name {namespace = "Handy", name = "PreferencesRow"})
    CString ->                              -- title : TBasicType TUTF8
    IO ()

-- | Sets the title of the preference represented by /@self@/.
-- 
-- /Since: 0.0.10/
preferencesRowSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesRow a) =>
    a
    -- ^ /@self@/: a t'GI.Handy.Objects.PreferencesRow.PreferencesRow'
    -> Maybe (T.Text)
    -- ^ /@title@/: the title, or 'P.Nothing'.
    -> m ()
preferencesRowSetTitle :: a -> Maybe Text -> m ()
preferencesRowSetTitle a
self Maybe Text
title = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesRow
self' <- a -> IO (Ptr PreferencesRow)
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 (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 (m :: * -> *) a. Monad m => a -> m a
return CString
jTitle'
    Ptr PreferencesRow -> CString -> IO ()
hdy_preferences_row_set_title Ptr PreferencesRow
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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PreferencesRowSetTitleMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsPreferencesRow a) => O.MethodInfo PreferencesRowSetTitleMethodInfo a signature where
    overloadedMethod = preferencesRowSetTitle

#endif

-- method PreferencesRow::set_use_underline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "PreferencesRow" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #HdyPreferencesRow"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_underline"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE if underlines in the text indicate mnemonics"
--                 , 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_row_set_use_underline" hdy_preferences_row_set_use_underline :: 
    Ptr PreferencesRow ->                   -- self : TInterface (Name {namespace = "Handy", name = "PreferencesRow"})
    CInt ->                                 -- use_underline : TBasicType TBoolean
    IO ()

-- | If true, an underline in the text of the title indicates the next character
-- should be used for the mnemonic accelerator key.
-- 
-- /Since: 0.0.10/
preferencesRowSetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesRow a) =>
    a
    -- ^ /@self@/: a t'GI.Handy.Objects.PreferencesRow.PreferencesRow'
    -> Bool
    -- ^ /@useUnderline@/: 'P.True' if underlines in the text indicate mnemonics
    -> m ()
preferencesRowSetUseUnderline :: a -> Bool -> m ()
preferencesRowSetUseUnderline a
self Bool
useUnderline = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesRow
self' <- a -> IO (Ptr PreferencesRow)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let useUnderline' :: CInt
useUnderline' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
useUnderline
    Ptr PreferencesRow -> CInt -> IO ()
hdy_preferences_row_set_use_underline Ptr PreferencesRow
self' CInt
useUnderline'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PreferencesRowSetUseUnderlineMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPreferencesRow a) => O.MethodInfo PreferencesRowSetUseUnderlineMethodInfo a signature where
    overloadedMethod = preferencesRowSetUseUnderline

#endif