{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.PreferencesView
(
PreferencesView(..) ,
IsPreferencesView ,
toPreferencesView ,
#if defined(ENABLE_OVERLOADING)
ResolvePreferencesViewMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PreferencesViewGetShowSearchEntryMethodInfo,
#endif
preferencesViewGetShowSearchEntry ,
#if defined(ENABLE_OVERLOADING)
PreferencesViewGetUseSidebarMethodInfo ,
#endif
preferencesViewGetUseSidebar ,
preferencesViewNew ,
#if defined(ENABLE_OVERLOADING)
PreferencesViewReapplyFilterMethodInfo ,
#endif
preferencesViewReapplyFilter ,
#if defined(ENABLE_OVERLOADING)
PreferencesViewSetShowSearchEntryMethodInfo,
#endif
preferencesViewSetShowSearchEntry ,
#if defined(ENABLE_OVERLOADING)
PreferencesViewSetUseSidebarMethodInfo ,
#endif
preferencesViewSetUseSidebar ,
#if defined(ENABLE_OVERLOADING)
PreferencesViewShowSearchEntryPropertyInfo,
#endif
constructPreferencesViewShowSearchEntry ,
getPreferencesViewShowSearchEntry ,
#if defined(ENABLE_OVERLOADING)
preferencesViewShowSearchEntry ,
#endif
setPreferencesViewShowSearchEntry ,
#if defined(ENABLE_OVERLOADING)
PreferencesViewUseSidebarPropertyInfo ,
#endif
constructPreferencesViewUseSidebar ,
getPreferencesViewUseSidebar ,
#if defined(ENABLE_OVERLOADING)
preferencesViewUseSidebar ,
#endif
setPreferencesViewUseSidebar ,
) 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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.Preferences as Dazzle.Preferences
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Enums as Gtk.Enums
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
#else
import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import {-# SOURCE #-} qualified GI.Dazzle.Interfaces.Preferences as Dazzle.Preferences
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
#endif
newtype PreferencesView = PreferencesView (SP.ManagedPtr PreferencesView)
deriving (PreferencesView -> PreferencesView -> Bool
(PreferencesView -> PreferencesView -> Bool)
-> (PreferencesView -> PreferencesView -> Bool)
-> Eq PreferencesView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PreferencesView -> PreferencesView -> Bool
== :: PreferencesView -> PreferencesView -> Bool
$c/= :: PreferencesView -> PreferencesView -> Bool
/= :: PreferencesView -> PreferencesView -> Bool
Eq)
instance SP.ManagedPtrNewtype PreferencesView where
toManagedPtr :: PreferencesView -> ManagedPtr PreferencesView
toManagedPtr (PreferencesView ManagedPtr PreferencesView
p) = ManagedPtr PreferencesView
p
foreign import ccall "dzl_preferences_view_get_type"
c_dzl_preferences_view_get_type :: IO B.Types.GType
instance B.Types.TypedObject PreferencesView where
glibType :: IO GType
glibType = IO GType
c_dzl_preferences_view_get_type
instance B.Types.GObject PreferencesView
class (SP.GObject o, O.IsDescendantOf PreferencesView o) => IsPreferencesView o
instance (SP.GObject o, O.IsDescendantOf PreferencesView o) => IsPreferencesView o
instance O.HasParentTypes PreferencesView
type instance O.ParentTypes PreferencesView = '[Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Dazzle.Preferences.Preferences, Gtk.Buildable.Buildable]
toPreferencesView :: (MIO.MonadIO m, IsPreferencesView o) => o -> m PreferencesView
toPreferencesView :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesView o) =>
o -> m PreferencesView
toPreferencesView = IO PreferencesView -> m PreferencesView
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PreferencesView -> m PreferencesView)
-> (o -> IO PreferencesView) -> o -> m PreferencesView
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr PreferencesView -> PreferencesView)
-> o -> IO PreferencesView
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr PreferencesView -> PreferencesView
PreferencesView
instance B.GValue.IsGValue (Maybe PreferencesView) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_preferences_view_get_type
gvalueSet_ :: Ptr GValue -> Maybe PreferencesView -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PreferencesView
P.Nothing = Ptr GValue -> Ptr PreferencesView -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr PreferencesView
forall a. Ptr a
FP.nullPtr :: FP.Ptr PreferencesView)
gvalueSet_ Ptr GValue
gv (P.Just PreferencesView
obj) = PreferencesView -> (Ptr PreferencesView -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PreferencesView
obj (Ptr GValue -> Ptr PreferencesView -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe PreferencesView)
gvalueGet_ Ptr GValue
gv = do
Ptr PreferencesView
ptr <- Ptr GValue -> IO (Ptr PreferencesView)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr PreferencesView)
if Ptr PreferencesView
ptr Ptr PreferencesView -> Ptr PreferencesView -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr PreferencesView
forall a. Ptr a
FP.nullPtr
then PreferencesView -> Maybe PreferencesView
forall a. a -> Maybe a
P.Just (PreferencesView -> Maybe PreferencesView)
-> IO PreferencesView -> IO (Maybe PreferencesView)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr PreferencesView -> PreferencesView)
-> Ptr PreferencesView -> IO PreferencesView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PreferencesView -> PreferencesView
PreferencesView Ptr PreferencesView
ptr
else Maybe PreferencesView -> IO (Maybe PreferencesView)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PreferencesView
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolvePreferencesViewMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolvePreferencesViewMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolvePreferencesViewMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolvePreferencesViewMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolvePreferencesViewMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolvePreferencesViewMethod "addCustom" o = Dazzle.Preferences.PreferencesAddCustomMethodInfo
ResolvePreferencesViewMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolvePreferencesViewMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolvePreferencesViewMethod "addFileChooser" o = Dazzle.Preferences.PreferencesAddFileChooserMethodInfo
ResolvePreferencesViewMethod "addFontButton" o = Dazzle.Preferences.PreferencesAddFontButtonMethodInfo
ResolvePreferencesViewMethod "addGroup" o = Dazzle.Preferences.PreferencesAddGroupMethodInfo
ResolvePreferencesViewMethod "addListGroup" o = Dazzle.Preferences.PreferencesAddListGroupMethodInfo
ResolvePreferencesViewMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolvePreferencesViewMethod "addPage" o = Dazzle.Preferences.PreferencesAddPageMethodInfo
ResolvePreferencesViewMethod "addRadio" o = Dazzle.Preferences.PreferencesAddRadioMethodInfo
ResolvePreferencesViewMethod "addSpinButton" o = Dazzle.Preferences.PreferencesAddSpinButtonMethodInfo
ResolvePreferencesViewMethod "addSwitch" o = Dazzle.Preferences.PreferencesAddSwitchMethodInfo
ResolvePreferencesViewMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolvePreferencesViewMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolvePreferencesViewMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolvePreferencesViewMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolvePreferencesViewMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolvePreferencesViewMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolvePreferencesViewMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolvePreferencesViewMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolvePreferencesViewMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolvePreferencesViewMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolvePreferencesViewMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolvePreferencesViewMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolvePreferencesViewMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolvePreferencesViewMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolvePreferencesViewMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolvePreferencesViewMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolvePreferencesViewMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolvePreferencesViewMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolvePreferencesViewMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolvePreferencesViewMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolvePreferencesViewMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolvePreferencesViewMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolvePreferencesViewMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolvePreferencesViewMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolvePreferencesViewMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolvePreferencesViewMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolvePreferencesViewMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolvePreferencesViewMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolvePreferencesViewMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolvePreferencesViewMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolvePreferencesViewMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolvePreferencesViewMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolvePreferencesViewMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolvePreferencesViewMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolvePreferencesViewMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolvePreferencesViewMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolvePreferencesViewMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolvePreferencesViewMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolvePreferencesViewMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolvePreferencesViewMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolvePreferencesViewMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolvePreferencesViewMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolvePreferencesViewMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolvePreferencesViewMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolvePreferencesViewMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolvePreferencesViewMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolvePreferencesViewMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolvePreferencesViewMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolvePreferencesViewMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolvePreferencesViewMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolvePreferencesViewMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolvePreferencesViewMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolvePreferencesViewMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolvePreferencesViewMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolvePreferencesViewMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolvePreferencesViewMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolvePreferencesViewMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolvePreferencesViewMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolvePreferencesViewMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolvePreferencesViewMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolvePreferencesViewMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolvePreferencesViewMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolvePreferencesViewMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolvePreferencesViewMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolvePreferencesViewMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolvePreferencesViewMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolvePreferencesViewMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolvePreferencesViewMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolvePreferencesViewMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolvePreferencesViewMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolvePreferencesViewMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolvePreferencesViewMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolvePreferencesViewMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolvePreferencesViewMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolvePreferencesViewMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolvePreferencesViewMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolvePreferencesViewMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolvePreferencesViewMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolvePreferencesViewMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolvePreferencesViewMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolvePreferencesViewMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolvePreferencesViewMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolvePreferencesViewMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolvePreferencesViewMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolvePreferencesViewMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolvePreferencesViewMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolvePreferencesViewMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolvePreferencesViewMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolvePreferencesViewMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolvePreferencesViewMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolvePreferencesViewMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolvePreferencesViewMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolvePreferencesViewMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolvePreferencesViewMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolvePreferencesViewMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolvePreferencesViewMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolvePreferencesViewMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolvePreferencesViewMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolvePreferencesViewMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolvePreferencesViewMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolvePreferencesViewMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolvePreferencesViewMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolvePreferencesViewMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolvePreferencesViewMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolvePreferencesViewMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolvePreferencesViewMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolvePreferencesViewMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolvePreferencesViewMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolvePreferencesViewMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolvePreferencesViewMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolvePreferencesViewMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolvePreferencesViewMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolvePreferencesViewMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolvePreferencesViewMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolvePreferencesViewMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolvePreferencesViewMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolvePreferencesViewMethod "reapplyFilter" o = PreferencesViewReapplyFilterMethodInfo
ResolvePreferencesViewMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolvePreferencesViewMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolvePreferencesViewMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolvePreferencesViewMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolvePreferencesViewMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolvePreferencesViewMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolvePreferencesViewMethod "removeId" o = Dazzle.Preferences.PreferencesRemoveIdMethodInfo
ResolvePreferencesViewMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolvePreferencesViewMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolvePreferencesViewMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolvePreferencesViewMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolvePreferencesViewMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolvePreferencesViewMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolvePreferencesViewMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolvePreferencesViewMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolvePreferencesViewMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolvePreferencesViewMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolvePreferencesViewMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolvePreferencesViewMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolvePreferencesViewMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolvePreferencesViewMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolvePreferencesViewMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolvePreferencesViewMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolvePreferencesViewMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolvePreferencesViewMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolvePreferencesViewMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolvePreferencesViewMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolvePreferencesViewMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolvePreferencesViewMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolvePreferencesViewMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolvePreferencesViewMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolvePreferencesViewMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolvePreferencesViewMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolvePreferencesViewMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolvePreferencesViewMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolvePreferencesViewMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolvePreferencesViewMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolvePreferencesViewMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolvePreferencesViewMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolvePreferencesViewMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolvePreferencesViewMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolvePreferencesViewMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolvePreferencesViewMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolvePreferencesViewMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolvePreferencesViewMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolvePreferencesViewMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolvePreferencesViewMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolvePreferencesViewMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolvePreferencesViewMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolvePreferencesViewMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolvePreferencesViewMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolvePreferencesViewMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolvePreferencesViewMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolvePreferencesViewMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
ResolvePreferencesViewMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolvePreferencesViewMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolvePreferencesViewMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolvePreferencesViewMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolvePreferencesViewMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolvePreferencesViewMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolvePreferencesViewMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolvePreferencesViewMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolvePreferencesViewMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolvePreferencesViewMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolvePreferencesViewMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolvePreferencesViewMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolvePreferencesViewMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolvePreferencesViewMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolvePreferencesViewMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolvePreferencesViewMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolvePreferencesViewMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
ResolvePreferencesViewMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolvePreferencesViewMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolvePreferencesViewMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolvePreferencesViewMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolvePreferencesViewMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolvePreferencesViewMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolvePreferencesViewMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolvePreferencesViewMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolvePreferencesViewMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolvePreferencesViewMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolvePreferencesViewMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolvePreferencesViewMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolvePreferencesViewMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolvePreferencesViewMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolvePreferencesViewMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolvePreferencesViewMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolvePreferencesViewMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolvePreferencesViewMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolvePreferencesViewMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolvePreferencesViewMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolvePreferencesViewMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolvePreferencesViewMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolvePreferencesViewMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolvePreferencesViewMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolvePreferencesViewMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolvePreferencesViewMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolvePreferencesViewMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolvePreferencesViewMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolvePreferencesViewMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolvePreferencesViewMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolvePreferencesViewMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolvePreferencesViewMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolvePreferencesViewMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolvePreferencesViewMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolvePreferencesViewMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolvePreferencesViewMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolvePreferencesViewMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolvePreferencesViewMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolvePreferencesViewMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolvePreferencesViewMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolvePreferencesViewMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolvePreferencesViewMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolvePreferencesViewMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolvePreferencesViewMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolvePreferencesViewMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolvePreferencesViewMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolvePreferencesViewMethod "getShowSearchEntry" o = PreferencesViewGetShowSearchEntryMethodInfo
ResolvePreferencesViewMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolvePreferencesViewMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolvePreferencesViewMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolvePreferencesViewMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolvePreferencesViewMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolvePreferencesViewMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolvePreferencesViewMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolvePreferencesViewMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolvePreferencesViewMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolvePreferencesViewMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolvePreferencesViewMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolvePreferencesViewMethod "getUseSidebar" o = PreferencesViewGetUseSidebarMethodInfo
ResolvePreferencesViewMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolvePreferencesViewMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolvePreferencesViewMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolvePreferencesViewMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolvePreferencesViewMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolvePreferencesViewMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolvePreferencesViewMethod "getWidget" o = Dazzle.Preferences.PreferencesGetWidgetMethodInfo
ResolvePreferencesViewMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolvePreferencesViewMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolvePreferencesViewMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolvePreferencesViewMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolvePreferencesViewMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolvePreferencesViewMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolvePreferencesViewMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolvePreferencesViewMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolvePreferencesViewMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolvePreferencesViewMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolvePreferencesViewMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolvePreferencesViewMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolvePreferencesViewMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolvePreferencesViewMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolvePreferencesViewMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolvePreferencesViewMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolvePreferencesViewMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolvePreferencesViewMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolvePreferencesViewMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolvePreferencesViewMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolvePreferencesViewMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolvePreferencesViewMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
ResolvePreferencesViewMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolvePreferencesViewMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolvePreferencesViewMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolvePreferencesViewMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolvePreferencesViewMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolvePreferencesViewMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolvePreferencesViewMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolvePreferencesViewMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolvePreferencesViewMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolvePreferencesViewMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolvePreferencesViewMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolvePreferencesViewMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolvePreferencesViewMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolvePreferencesViewMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolvePreferencesViewMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolvePreferencesViewMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolvePreferencesViewMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolvePreferencesViewMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolvePreferencesViewMethod "setPage" o = Dazzle.Preferences.PreferencesSetPageMethodInfo
ResolvePreferencesViewMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolvePreferencesViewMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolvePreferencesViewMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolvePreferencesViewMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolvePreferencesViewMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolvePreferencesViewMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolvePreferencesViewMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolvePreferencesViewMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolvePreferencesViewMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolvePreferencesViewMethod "setShowSearchEntry" o = PreferencesViewSetShowSearchEntryMethodInfo
ResolvePreferencesViewMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolvePreferencesViewMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolvePreferencesViewMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolvePreferencesViewMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolvePreferencesViewMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolvePreferencesViewMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolvePreferencesViewMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolvePreferencesViewMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolvePreferencesViewMethod "setUseSidebar" o = PreferencesViewSetUseSidebarMethodInfo
ResolvePreferencesViewMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolvePreferencesViewMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolvePreferencesViewMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolvePreferencesViewMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolvePreferencesViewMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolvePreferencesViewMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolvePreferencesViewMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePreferencesViewMethod t PreferencesView, O.OverloadedMethod info PreferencesView p) => OL.IsLabel t (PreferencesView -> 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 ~ ResolvePreferencesViewMethod t PreferencesView, O.OverloadedMethod info PreferencesView p, R.HasField t PreferencesView p) => R.HasField t PreferencesView p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePreferencesViewMethod t PreferencesView, O.OverloadedMethodInfo info PreferencesView) => OL.IsLabel t (O.MethodProxy info PreferencesView) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getPreferencesViewShowSearchEntry :: (MonadIO m, IsPreferencesView o) => o -> m Bool
getPreferencesViewShowSearchEntry :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesView o) =>
o -> m Bool
getPreferencesViewShowSearchEntry o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"show-search-entry"
setPreferencesViewShowSearchEntry :: (MonadIO m, IsPreferencesView o) => o -> Bool -> m ()
setPreferencesViewShowSearchEntry :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesView o) =>
o -> Bool -> m ()
setPreferencesViewShowSearchEntry o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"show-search-entry" Bool
val
constructPreferencesViewShowSearchEntry :: (IsPreferencesView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPreferencesViewShowSearchEntry :: forall o (m :: * -> *).
(IsPreferencesView o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPreferencesViewShowSearchEntry Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"show-search-entry" Bool
val
#if defined(ENABLE_OVERLOADING)
data PreferencesViewShowSearchEntryPropertyInfo
instance AttrInfo PreferencesViewShowSearchEntryPropertyInfo where
type AttrAllowedOps PreferencesViewShowSearchEntryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint PreferencesViewShowSearchEntryPropertyInfo = IsPreferencesView
type AttrSetTypeConstraint PreferencesViewShowSearchEntryPropertyInfo = (~) Bool
type AttrTransferTypeConstraint PreferencesViewShowSearchEntryPropertyInfo = (~) Bool
type AttrTransferType PreferencesViewShowSearchEntryPropertyInfo = Bool
type AttrGetType PreferencesViewShowSearchEntryPropertyInfo = Bool
type AttrLabel PreferencesViewShowSearchEntryPropertyInfo = "show-search-entry"
type AttrOrigin PreferencesViewShowSearchEntryPropertyInfo = PreferencesView
attrGet = getPreferencesViewShowSearchEntry
attrSet = setPreferencesViewShowSearchEntry
attrTransfer _ v = do
return v
attrConstruct = constructPreferencesViewShowSearchEntry
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.PreferencesView.showSearchEntry"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-PreferencesView.html#g:attr:showSearchEntry"
})
#endif
getPreferencesViewUseSidebar :: (MonadIO m, IsPreferencesView o) => o -> m Bool
o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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-sidebar"
setPreferencesViewUseSidebar :: (MonadIO m, IsPreferencesView o) => o -> Bool -> m ()
o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-sidebar" Bool
val
constructPreferencesViewUseSidebar :: (IsPreferencesView o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-sidebar" Bool
val
#if defined(ENABLE_OVERLOADING)
data PreferencesViewUseSidebarPropertyInfo
instance AttrInfo PreferencesViewUseSidebarPropertyInfo where
type AttrAllowedOps PreferencesViewUseSidebarPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint PreferencesViewUseSidebarPropertyInfo = IsPreferencesView
type AttrSetTypeConstraint PreferencesViewUseSidebarPropertyInfo = (~) Bool
type AttrTransferTypeConstraint PreferencesViewUseSidebarPropertyInfo = (~) Bool
type AttrTransferType PreferencesViewUseSidebarPropertyInfo = Bool
type AttrGetType PreferencesViewUseSidebarPropertyInfo = Bool
type AttrLabel PreferencesViewUseSidebarPropertyInfo = "use-sidebar"
type AttrOrigin PreferencesViewUseSidebarPropertyInfo = PreferencesView
attrGet = getPreferencesViewUseSidebar
attrSet = setPreferencesViewUseSidebar
attrTransfer _ v = do
return v
attrConstruct = constructPreferencesViewUseSidebar
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.PreferencesView.useSidebar"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-PreferencesView.html#g:attr:useSidebar"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PreferencesView
type instance O.AttributeList PreferencesView = PreferencesViewAttributeList
type PreferencesViewAttributeList = ('[ '("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), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("showSearchEntry", PreferencesViewShowSearchEntryPropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useSidebar", PreferencesViewUseSidebarPropertyInfo), '("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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
preferencesViewShowSearchEntry :: AttrLabelProxy "showSearchEntry"
preferencesViewShowSearchEntry = AttrLabelProxy
preferencesViewUseSidebar :: AttrLabelProxy "useSidebar"
preferencesViewUseSidebar = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PreferencesView = PreferencesViewSignalList
type PreferencesViewSignalList = ('[ '("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, DK.Type)])
#endif
foreign import ccall "dzl_preferences_view_new" dzl_preferences_view_new ::
IO (Ptr PreferencesView)
preferencesViewNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m PreferencesView
preferencesViewNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m PreferencesView
preferencesViewNew = IO PreferencesView -> m PreferencesView
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PreferencesView -> m PreferencesView)
-> IO PreferencesView -> m PreferencesView
forall a b. (a -> b) -> a -> b
$ do
Ptr PreferencesView
result <- IO (Ptr PreferencesView)
dzl_preferences_view_new
Text -> Ptr PreferencesView -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"preferencesViewNew" Ptr PreferencesView
result
PreferencesView
result' <- ((ManagedPtr PreferencesView -> PreferencesView)
-> Ptr PreferencesView -> IO PreferencesView
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PreferencesView -> PreferencesView
PreferencesView) Ptr PreferencesView
result
PreferencesView -> IO PreferencesView
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PreferencesView
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_preferences_view_get_show_search_entry" dzl_preferences_view_get_show_search_entry ::
Ptr PreferencesView ->
IO CInt
preferencesViewGetShowSearchEntry ::
(B.CallStack.HasCallStack, MonadIO m, IsPreferencesView a) =>
a
-> m Bool
preferencesViewGetShowSearchEntry :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesView a) =>
a -> m Bool
preferencesViewGetShowSearchEntry a
self = IO Bool -> m Bool
forall a. IO a -> m a
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 PreferencesView
self' <- a -> IO (Ptr PreferencesView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr PreferencesView -> IO CInt
dzl_preferences_view_get_show_search_entry Ptr PreferencesView
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PreferencesViewGetShowSearchEntryMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPreferencesView a) => O.OverloadedMethod PreferencesViewGetShowSearchEntryMethodInfo a signature where
overloadedMethod = preferencesViewGetShowSearchEntry
instance O.OverloadedMethodInfo PreferencesViewGetShowSearchEntryMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.PreferencesView.preferencesViewGetShowSearchEntry",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-PreferencesView.html#v:preferencesViewGetShowSearchEntry"
})
#endif
foreign import ccall "dzl_preferences_view_get_use_sidebar" ::
Ptr PreferencesView ->
IO CInt
preferencesViewGetUseSidebar ::
(B.CallStack.HasCallStack, MonadIO m, IsPreferencesView a) =>
a
-> m Bool
a
self = IO Bool -> m Bool
forall a. IO a -> m a
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 PreferencesView
self' <- a -> IO (Ptr PreferencesView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CInt
result <- Ptr PreferencesView -> IO CInt
dzl_preferences_view_get_use_sidebar Ptr PreferencesView
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PreferencesViewGetUseSidebarMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPreferencesView a) => O.OverloadedMethod PreferencesViewGetUseSidebarMethodInfo a signature where
overloadedMethod = preferencesViewGetUseSidebar
instance O.OverloadedMethodInfo PreferencesViewGetUseSidebarMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.PreferencesView.preferencesViewGetUseSidebar",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-PreferencesView.html#v:preferencesViewGetUseSidebar"
})
#endif
foreign import ccall "dzl_preferences_view_reapply_filter" dzl_preferences_view_reapply_filter ::
Ptr PreferencesView ->
IO ()
preferencesViewReapplyFilter ::
(B.CallStack.HasCallStack, MonadIO m, IsPreferencesView a) =>
a
-> m ()
preferencesViewReapplyFilter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesView a) =>
a -> m ()
preferencesViewReapplyFilter a
self = 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 PreferencesView
self' <- a -> IO (Ptr PreferencesView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr PreferencesView -> IO ()
dzl_preferences_view_reapply_filter Ptr PreferencesView
self'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PreferencesViewReapplyFilterMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPreferencesView a) => O.OverloadedMethod PreferencesViewReapplyFilterMethodInfo a signature where
overloadedMethod = preferencesViewReapplyFilter
instance O.OverloadedMethodInfo PreferencesViewReapplyFilterMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.PreferencesView.preferencesViewReapplyFilter",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-PreferencesView.html#v:preferencesViewReapplyFilter"
})
#endif
foreign import ccall "dzl_preferences_view_set_show_search_entry" dzl_preferences_view_set_show_search_entry ::
Ptr PreferencesView ->
CInt ->
IO ()
preferencesViewSetShowSearchEntry ::
(B.CallStack.HasCallStack, MonadIO m, IsPreferencesView a) =>
a
-> Bool
-> m ()
preferencesViewSetShowSearchEntry :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesView a) =>
a -> Bool -> m ()
preferencesViewSetShowSearchEntry a
self Bool
showSearchEntry = 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 PreferencesView
self' <- a -> IO (Ptr PreferencesView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let showSearchEntry' :: CInt
showSearchEntry' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
showSearchEntry
Ptr PreferencesView -> CInt -> IO ()
dzl_preferences_view_set_show_search_entry Ptr PreferencesView
self' CInt
showSearchEntry'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PreferencesViewSetShowSearchEntryMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPreferencesView a) => O.OverloadedMethod PreferencesViewSetShowSearchEntryMethodInfo a signature where
overloadedMethod = preferencesViewSetShowSearchEntry
instance O.OverloadedMethodInfo PreferencesViewSetShowSearchEntryMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.PreferencesView.preferencesViewSetShowSearchEntry",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-PreferencesView.html#v:preferencesViewSetShowSearchEntry"
})
#endif
foreign import ccall "dzl_preferences_view_set_use_sidebar" ::
Ptr PreferencesView ->
CInt ->
IO ()
preferencesViewSetUseSidebar ::
(B.CallStack.HasCallStack, MonadIO m, IsPreferencesView a) =>
a
-> Bool
-> m ()
a
self Bool
useSidebar = 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 PreferencesView
self' <- a -> IO (Ptr PreferencesView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
let useSidebar' :: CInt
useSidebar' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
useSidebar
Ptr PreferencesView -> CInt -> IO ()
dzl_preferences_view_set_use_sidebar Ptr PreferencesView
self' CInt
useSidebar'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PreferencesViewSetUseSidebarMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPreferencesView a) => O.OverloadedMethod PreferencesViewSetUseSidebarMethodInfo a signature where
overloadedMethod = preferencesViewSetUseSidebar
instance O.OverloadedMethodInfo PreferencesViewSetUseSidebarMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.PreferencesView.preferencesViewSetUseSidebar",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-PreferencesView.html#v:preferencesViewSetUseSidebar"
})
#endif