{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.ScaleButton
(
ScaleButton(..) ,
IsScaleButton ,
toScaleButton ,
#if defined(ENABLE_OVERLOADING)
ResolveScaleButtonMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ScaleButtonGetAdjustmentMethodInfo ,
#endif
scaleButtonGetAdjustment ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonGetMinusButtonMethodInfo ,
#endif
scaleButtonGetMinusButton ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonGetPlusButtonMethodInfo ,
#endif
scaleButtonGetPlusButton ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonGetPopupMethodInfo ,
#endif
scaleButtonGetPopup ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonGetValueMethodInfo ,
#endif
scaleButtonGetValue ,
scaleButtonNew ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonSetAdjustmentMethodInfo ,
#endif
scaleButtonSetAdjustment ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonSetIconsMethodInfo ,
#endif
scaleButtonSetIcons ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonSetValueMethodInfo ,
#endif
scaleButtonSetValue ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonAdjustmentPropertyInfo ,
#endif
constructScaleButtonAdjustment ,
getScaleButtonAdjustment ,
#if defined(ENABLE_OVERLOADING)
scaleButtonAdjustment ,
#endif
setScaleButtonAdjustment ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonIconsPropertyInfo ,
#endif
constructScaleButtonIcons ,
getScaleButtonIcons ,
#if defined(ENABLE_OVERLOADING)
scaleButtonIcons ,
#endif
setScaleButtonIcons ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonSizePropertyInfo ,
#endif
constructScaleButtonSize ,
getScaleButtonSize ,
#if defined(ENABLE_OVERLOADING)
scaleButtonSize ,
#endif
setScaleButtonSize ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonValuePropertyInfo ,
#endif
constructScaleButtonValue ,
getScaleButtonValue ,
#if defined(ENABLE_OVERLOADING)
scaleButtonValue ,
#endif
setScaleButtonValue ,
ScaleButtonPopdownCallback ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonPopdownSignalInfo ,
#endif
afterScaleButtonPopdown ,
onScaleButtonPopdown ,
ScaleButtonPopupCallback ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonPopupSignalInfo ,
#endif
afterScaleButtonPopup ,
onScaleButtonPopup ,
ScaleButtonValueChangedCallback ,
#if defined(ENABLE_OVERLOADING)
ScaleButtonValueChangedSignalInfo ,
#endif
afterScaleButtonValueChanged ,
onScaleButtonValueChanged ,
) 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 GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Actionable as Gtk.Actionable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Activatable as Gtk.Activatable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Adjustment as Gtk.Adjustment
import {-# SOURCE #-} qualified GI.Gtk.Objects.Bin as Gtk.Bin
import {-# SOURCE #-} qualified GI.Gtk.Objects.Button as Gtk.Button
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype ScaleButton = ScaleButton (SP.ManagedPtr ScaleButton)
deriving (ScaleButton -> ScaleButton -> Bool
(ScaleButton -> ScaleButton -> Bool)
-> (ScaleButton -> ScaleButton -> Bool) -> Eq ScaleButton
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScaleButton -> ScaleButton -> Bool
== :: ScaleButton -> ScaleButton -> Bool
$c/= :: ScaleButton -> ScaleButton -> Bool
/= :: ScaleButton -> ScaleButton -> Bool
Eq)
instance SP.ManagedPtrNewtype ScaleButton where
toManagedPtr :: ScaleButton -> ManagedPtr ScaleButton
toManagedPtr (ScaleButton ManagedPtr ScaleButton
p) = ManagedPtr ScaleButton
p
foreign import ccall "gtk_scale_button_get_type"
c_gtk_scale_button_get_type :: IO B.Types.GType
instance B.Types.TypedObject ScaleButton where
glibType :: IO GType
glibType = IO GType
c_gtk_scale_button_get_type
instance B.Types.GObject ScaleButton
class (SP.GObject o, O.IsDescendantOf ScaleButton o) => IsScaleButton o
instance (SP.GObject o, O.IsDescendantOf ScaleButton o) => IsScaleButton o
instance O.HasParentTypes ScaleButton
type instance O.ParentTypes ScaleButton = '[Gtk.Button.Button, Gtk.Bin.Bin, Gtk.Container.Container, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Actionable.Actionable, Gtk.Activatable.Activatable, Gtk.Buildable.Buildable, Gtk.Orientable.Orientable]
toScaleButton :: (MIO.MonadIO m, IsScaleButton o) => o -> m ScaleButton
toScaleButton :: forall (m :: * -> *) o.
(MonadIO m, IsScaleButton o) =>
o -> m ScaleButton
toScaleButton = IO ScaleButton -> m ScaleButton
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ScaleButton -> m ScaleButton)
-> (o -> IO ScaleButton) -> o -> m ScaleButton
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ScaleButton -> ScaleButton) -> o -> IO ScaleButton
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr ScaleButton -> ScaleButton
ScaleButton
instance B.GValue.IsGValue (Maybe ScaleButton) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_scale_button_get_type
gvalueSet_ :: Ptr GValue -> Maybe ScaleButton -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ScaleButton
P.Nothing = Ptr GValue -> Ptr ScaleButton -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ScaleButton
forall a. Ptr a
FP.nullPtr :: FP.Ptr ScaleButton)
gvalueSet_ Ptr GValue
gv (P.Just ScaleButton
obj) = ScaleButton -> (Ptr ScaleButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ScaleButton
obj (Ptr GValue -> Ptr ScaleButton -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe ScaleButton)
gvalueGet_ Ptr GValue
gv = do
Ptr ScaleButton
ptr <- Ptr GValue -> IO (Ptr ScaleButton)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ScaleButton)
if Ptr ScaleButton
ptr Ptr ScaleButton -> Ptr ScaleButton -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ScaleButton
forall a. Ptr a
FP.nullPtr
then ScaleButton -> Maybe ScaleButton
forall a. a -> Maybe a
P.Just (ScaleButton -> Maybe ScaleButton)
-> IO ScaleButton -> IO (Maybe ScaleButton)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ScaleButton -> ScaleButton)
-> Ptr ScaleButton -> IO ScaleButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ScaleButton -> ScaleButton
ScaleButton Ptr ScaleButton
ptr
else Maybe ScaleButton -> IO (Maybe ScaleButton)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ScaleButton
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveScaleButtonMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveScaleButtonMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
ResolveScaleButtonMethod "add" o = Gtk.Container.ContainerAddMethodInfo
ResolveScaleButtonMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
ResolveScaleButtonMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
ResolveScaleButtonMethod "addDeviceEvents" o = Gtk.Widget.WidgetAddDeviceEventsMethodInfo
ResolveScaleButtonMethod "addEvents" o = Gtk.Widget.WidgetAddEventsMethodInfo
ResolveScaleButtonMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
ResolveScaleButtonMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
ResolveScaleButtonMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveScaleButtonMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveScaleButtonMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
ResolveScaleButtonMethod "checkResize" o = Gtk.Container.ContainerCheckResizeMethodInfo
ResolveScaleButtonMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
ResolveScaleButtonMethod "childGetProperty" o = Gtk.Container.ContainerChildGetPropertyMethodInfo
ResolveScaleButtonMethod "childNotify" o = Gtk.Container.ContainerChildNotifyMethodInfo
ResolveScaleButtonMethod "childNotifyByPspec" o = Gtk.Container.ContainerChildNotifyByPspecMethodInfo
ResolveScaleButtonMethod "childSetProperty" o = Gtk.Container.ContainerChildSetPropertyMethodInfo
ResolveScaleButtonMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
ResolveScaleButtonMethod "classPath" o = Gtk.Widget.WidgetClassPathMethodInfo
ResolveScaleButtonMethod "clicked" o = Gtk.Button.ButtonClickedMethodInfo
ResolveScaleButtonMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
ResolveScaleButtonMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
ResolveScaleButtonMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
ResolveScaleButtonMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
ResolveScaleButtonMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
ResolveScaleButtonMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
ResolveScaleButtonMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
ResolveScaleButtonMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
ResolveScaleButtonMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
ResolveScaleButtonMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
ResolveScaleButtonMethod "doSetRelatedAction" o = Gtk.Activatable.ActivatableDoSetRelatedActionMethodInfo
ResolveScaleButtonMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
ResolveScaleButtonMethod "dragBeginWithCoordinates" o = Gtk.Widget.WidgetDragBeginWithCoordinatesMethodInfo
ResolveScaleButtonMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
ResolveScaleButtonMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
ResolveScaleButtonMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
ResolveScaleButtonMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
ResolveScaleButtonMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
ResolveScaleButtonMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
ResolveScaleButtonMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
ResolveScaleButtonMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
ResolveScaleButtonMethod "dragDestSetProxy" o = Gtk.Widget.WidgetDragDestSetProxyMethodInfo
ResolveScaleButtonMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
ResolveScaleButtonMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
ResolveScaleButtonMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
ResolveScaleButtonMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
ResolveScaleButtonMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
ResolveScaleButtonMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
ResolveScaleButtonMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
ResolveScaleButtonMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
ResolveScaleButtonMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
ResolveScaleButtonMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
ResolveScaleButtonMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
ResolveScaleButtonMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
ResolveScaleButtonMethod "dragSourceSetIconPixbuf" o = Gtk.Widget.WidgetDragSourceSetIconPixbufMethodInfo
ResolveScaleButtonMethod "dragSourceSetIconStock" o = Gtk.Widget.WidgetDragSourceSetIconStockMethodInfo
ResolveScaleButtonMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
ResolveScaleButtonMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
ResolveScaleButtonMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
ResolveScaleButtonMethod "draw" o = Gtk.Widget.WidgetDrawMethodInfo
ResolveScaleButtonMethod "ensureStyle" o = Gtk.Widget.WidgetEnsureStyleMethodInfo
ResolveScaleButtonMethod "enter" o = Gtk.Button.ButtonEnterMethodInfo
ResolveScaleButtonMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
ResolveScaleButtonMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
ResolveScaleButtonMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
ResolveScaleButtonMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveScaleButtonMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
ResolveScaleButtonMethod "freezeChildNotify" o = Gtk.Widget.WidgetFreezeChildNotifyMethodInfo
ResolveScaleButtonMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveScaleButtonMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveScaleButtonMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
ResolveScaleButtonMethod "grabDefault" o = Gtk.Widget.WidgetGrabDefaultMethodInfo
ResolveScaleButtonMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
ResolveScaleButtonMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
ResolveScaleButtonMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
ResolveScaleButtonMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
ResolveScaleButtonMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
ResolveScaleButtonMethod "hasRcStyle" o = Gtk.Widget.WidgetHasRcStyleMethodInfo
ResolveScaleButtonMethod "hasScreen" o = Gtk.Widget.WidgetHasScreenMethodInfo
ResolveScaleButtonMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
ResolveScaleButtonMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
ResolveScaleButtonMethod "hideOnDelete" o = Gtk.Widget.WidgetHideOnDeleteMethodInfo
ResolveScaleButtonMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
ResolveScaleButtonMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
ResolveScaleButtonMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
ResolveScaleButtonMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
ResolveScaleButtonMethod "intersect" o = Gtk.Widget.WidgetIntersectMethodInfo
ResolveScaleButtonMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
ResolveScaleButtonMethod "isComposited" o = Gtk.Widget.WidgetIsCompositedMethodInfo
ResolveScaleButtonMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
ResolveScaleButtonMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveScaleButtonMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
ResolveScaleButtonMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
ResolveScaleButtonMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
ResolveScaleButtonMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
ResolveScaleButtonMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
ResolveScaleButtonMethod "leave" o = Gtk.Button.ButtonLeaveMethodInfo
ResolveScaleButtonMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
ResolveScaleButtonMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
ResolveScaleButtonMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
ResolveScaleButtonMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
ResolveScaleButtonMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
ResolveScaleButtonMethod "modifyBase" o = Gtk.Widget.WidgetModifyBaseMethodInfo
ResolveScaleButtonMethod "modifyBg" o = Gtk.Widget.WidgetModifyBgMethodInfo
ResolveScaleButtonMethod "modifyCursor" o = Gtk.Widget.WidgetModifyCursorMethodInfo
ResolveScaleButtonMethod "modifyFg" o = Gtk.Widget.WidgetModifyFgMethodInfo
ResolveScaleButtonMethod "modifyFont" o = Gtk.Widget.WidgetModifyFontMethodInfo
ResolveScaleButtonMethod "modifyStyle" o = Gtk.Widget.WidgetModifyStyleMethodInfo
ResolveScaleButtonMethod "modifyText" o = Gtk.Widget.WidgetModifyTextMethodInfo
ResolveScaleButtonMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveScaleButtonMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveScaleButtonMethod "overrideBackgroundColor" o = Gtk.Widget.WidgetOverrideBackgroundColorMethodInfo
ResolveScaleButtonMethod "overrideColor" o = Gtk.Widget.WidgetOverrideColorMethodInfo
ResolveScaleButtonMethod "overrideCursor" o = Gtk.Widget.WidgetOverrideCursorMethodInfo
ResolveScaleButtonMethod "overrideFont" o = Gtk.Widget.WidgetOverrideFontMethodInfo
ResolveScaleButtonMethod "overrideSymbolicColor" o = Gtk.Widget.WidgetOverrideSymbolicColorMethodInfo
ResolveScaleButtonMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
ResolveScaleButtonMethod "path" o = Gtk.Widget.WidgetPathMethodInfo
ResolveScaleButtonMethod "pressed" o = Gtk.Button.ButtonPressedMethodInfo
ResolveScaleButtonMethod "propagateDraw" o = Gtk.Container.ContainerPropagateDrawMethodInfo
ResolveScaleButtonMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
ResolveScaleButtonMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
ResolveScaleButtonMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
ResolveScaleButtonMethod "queueDrawArea" o = Gtk.Widget.WidgetQueueDrawAreaMethodInfo
ResolveScaleButtonMethod "queueDrawRegion" o = Gtk.Widget.WidgetQueueDrawRegionMethodInfo
ResolveScaleButtonMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
ResolveScaleButtonMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
ResolveScaleButtonMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
ResolveScaleButtonMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveScaleButtonMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveScaleButtonMethod "regionIntersect" o = Gtk.Widget.WidgetRegionIntersectMethodInfo
ResolveScaleButtonMethod "registerWindow" o = Gtk.Widget.WidgetRegisterWindowMethodInfo
ResolveScaleButtonMethod "released" o = Gtk.Button.ButtonReleasedMethodInfo
ResolveScaleButtonMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
ResolveScaleButtonMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
ResolveScaleButtonMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
ResolveScaleButtonMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
ResolveScaleButtonMethod "renderIcon" o = Gtk.Widget.WidgetRenderIconMethodInfo
ResolveScaleButtonMethod "renderIconPixbuf" o = Gtk.Widget.WidgetRenderIconPixbufMethodInfo
ResolveScaleButtonMethod "reparent" o = Gtk.Widget.WidgetReparentMethodInfo
ResolveScaleButtonMethod "resetRcStyles" o = Gtk.Widget.WidgetResetRcStylesMethodInfo
ResolveScaleButtonMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
ResolveScaleButtonMethod "resizeChildren" o = Gtk.Container.ContainerResizeChildrenMethodInfo
ResolveScaleButtonMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveScaleButtonMethod "sendExpose" o = Gtk.Widget.WidgetSendExposeMethodInfo
ResolveScaleButtonMethod "sendFocusChange" o = Gtk.Widget.WidgetSendFocusChangeMethodInfo
ResolveScaleButtonMethod "shapeCombineRegion" o = Gtk.Widget.WidgetShapeCombineRegionMethodInfo
ResolveScaleButtonMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
ResolveScaleButtonMethod "showAll" o = Gtk.Widget.WidgetShowAllMethodInfo
ResolveScaleButtonMethod "showNow" o = Gtk.Widget.WidgetShowNowMethodInfo
ResolveScaleButtonMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
ResolveScaleButtonMethod "sizeAllocateWithBaseline" o = Gtk.Widget.WidgetSizeAllocateWithBaselineMethodInfo
ResolveScaleButtonMethod "sizeRequest" o = Gtk.Widget.WidgetSizeRequestMethodInfo
ResolveScaleButtonMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveScaleButtonMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveScaleButtonMethod "styleAttach" o = Gtk.Widget.WidgetStyleAttachMethodInfo
ResolveScaleButtonMethod "styleGetProperty" o = Gtk.Widget.WidgetStyleGetPropertyMethodInfo
ResolveScaleButtonMethod "syncActionProperties" o = Gtk.Activatable.ActivatableSyncActionPropertiesMethodInfo
ResolveScaleButtonMethod "thawChildNotify" o = Gtk.Widget.WidgetThawChildNotifyMethodInfo
ResolveScaleButtonMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveScaleButtonMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
ResolveScaleButtonMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
ResolveScaleButtonMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
ResolveScaleButtonMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
ResolveScaleButtonMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
ResolveScaleButtonMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveScaleButtonMethod "unregisterWindow" o = Gtk.Widget.WidgetUnregisterWindowMethodInfo
ResolveScaleButtonMethod "unsetFocusChain" o = Gtk.Container.ContainerUnsetFocusChainMethodInfo
ResolveScaleButtonMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
ResolveScaleButtonMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveScaleButtonMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
ResolveScaleButtonMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
ResolveScaleButtonMethod "getActionName" o = Gtk.Actionable.ActionableGetActionNameMethodInfo
ResolveScaleButtonMethod "getActionTargetValue" o = Gtk.Actionable.ActionableGetActionTargetValueMethodInfo
ResolveScaleButtonMethod "getAdjustment" o = ScaleButtonGetAdjustmentMethodInfo
ResolveScaleButtonMethod "getAlignment" o = Gtk.Button.ButtonGetAlignmentMethodInfo
ResolveScaleButtonMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
ResolveScaleButtonMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
ResolveScaleButtonMethod "getAllocatedSize" o = Gtk.Widget.WidgetGetAllocatedSizeMethodInfo
ResolveScaleButtonMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
ResolveScaleButtonMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
ResolveScaleButtonMethod "getAlwaysShowImage" o = Gtk.Button.ButtonGetAlwaysShowImageMethodInfo
ResolveScaleButtonMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
ResolveScaleButtonMethod "getAppPaintable" o = Gtk.Widget.WidgetGetAppPaintableMethodInfo
ResolveScaleButtonMethod "getBorderWidth" o = Gtk.Container.ContainerGetBorderWidthMethodInfo
ResolveScaleButtonMethod "getCanDefault" o = Gtk.Widget.WidgetGetCanDefaultMethodInfo
ResolveScaleButtonMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
ResolveScaleButtonMethod "getChild" o = Gtk.Bin.BinGetChildMethodInfo
ResolveScaleButtonMethod "getChildRequisition" o = Gtk.Widget.WidgetGetChildRequisitionMethodInfo
ResolveScaleButtonMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
ResolveScaleButtonMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
ResolveScaleButtonMethod "getClip" o = Gtk.Widget.WidgetGetClipMethodInfo
ResolveScaleButtonMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
ResolveScaleButtonMethod "getCompositeName" o = Gtk.Widget.WidgetGetCompositeNameMethodInfo
ResolveScaleButtonMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveScaleButtonMethod "getDeviceEnabled" o = Gtk.Widget.WidgetGetDeviceEnabledMethodInfo
ResolveScaleButtonMethod "getDeviceEvents" o = Gtk.Widget.WidgetGetDeviceEventsMethodInfo
ResolveScaleButtonMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
ResolveScaleButtonMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
ResolveScaleButtonMethod "getDoubleBuffered" o = Gtk.Widget.WidgetGetDoubleBufferedMethodInfo
ResolveScaleButtonMethod "getEventWindow" o = Gtk.Button.ButtonGetEventWindowMethodInfo
ResolveScaleButtonMethod "getEvents" o = Gtk.Widget.WidgetGetEventsMethodInfo
ResolveScaleButtonMethod "getFocusChain" o = Gtk.Container.ContainerGetFocusChainMethodInfo
ResolveScaleButtonMethod "getFocusChild" o = Gtk.Container.ContainerGetFocusChildMethodInfo
ResolveScaleButtonMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
ResolveScaleButtonMethod "getFocusOnClick" o = Gtk.Button.ButtonGetFocusOnClickMethodInfo
ResolveScaleButtonMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
ResolveScaleButtonMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
ResolveScaleButtonMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
ResolveScaleButtonMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
ResolveScaleButtonMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
ResolveScaleButtonMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
ResolveScaleButtonMethod "getHasWindow" o = Gtk.Widget.WidgetGetHasWindowMethodInfo
ResolveScaleButtonMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
ResolveScaleButtonMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
ResolveScaleButtonMethod "getImage" o = Gtk.Button.ButtonGetImageMethodInfo
ResolveScaleButtonMethod "getImagePosition" o = Gtk.Button.ButtonGetImagePositionMethodInfo
ResolveScaleButtonMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
ResolveScaleButtonMethod "getLabel" o = Gtk.Button.ButtonGetLabelMethodInfo
ResolveScaleButtonMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
ResolveScaleButtonMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
ResolveScaleButtonMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
ResolveScaleButtonMethod "getMarginLeft" o = Gtk.Widget.WidgetGetMarginLeftMethodInfo
ResolveScaleButtonMethod "getMarginRight" o = Gtk.Widget.WidgetGetMarginRightMethodInfo
ResolveScaleButtonMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
ResolveScaleButtonMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
ResolveScaleButtonMethod "getMinusButton" o = ScaleButtonGetMinusButtonMethodInfo
ResolveScaleButtonMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
ResolveScaleButtonMethod "getModifierStyle" o = Gtk.Widget.WidgetGetModifierStyleMethodInfo
ResolveScaleButtonMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
ResolveScaleButtonMethod "getNoShowAll" o = Gtk.Widget.WidgetGetNoShowAllMethodInfo
ResolveScaleButtonMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
ResolveScaleButtonMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
ResolveScaleButtonMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
ResolveScaleButtonMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
ResolveScaleButtonMethod "getParentWindow" o = Gtk.Widget.WidgetGetParentWindowMethodInfo
ResolveScaleButtonMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
ResolveScaleButtonMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
ResolveScaleButtonMethod "getPlusButton" o = ScaleButtonGetPlusButtonMethodInfo
ResolveScaleButtonMethod "getPointer" o = Gtk.Widget.WidgetGetPointerMethodInfo
ResolveScaleButtonMethod "getPopup" o = ScaleButtonGetPopupMethodInfo
ResolveScaleButtonMethod "getPreferredHeight" o = Gtk.Widget.WidgetGetPreferredHeightMethodInfo
ResolveScaleButtonMethod "getPreferredHeightAndBaselineForWidth" o = Gtk.Widget.WidgetGetPreferredHeightAndBaselineForWidthMethodInfo
ResolveScaleButtonMethod "getPreferredHeightForWidth" o = Gtk.Widget.WidgetGetPreferredHeightForWidthMethodInfo
ResolveScaleButtonMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
ResolveScaleButtonMethod "getPreferredWidth" o = Gtk.Widget.WidgetGetPreferredWidthMethodInfo
ResolveScaleButtonMethod "getPreferredWidthForHeight" o = Gtk.Widget.WidgetGetPreferredWidthForHeightMethodInfo
ResolveScaleButtonMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveScaleButtonMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveScaleButtonMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
ResolveScaleButtonMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
ResolveScaleButtonMethod "getRelatedAction" o = Gtk.Activatable.ActivatableGetRelatedActionMethodInfo
ResolveScaleButtonMethod "getRelief" o = Gtk.Button.ButtonGetReliefMethodInfo
ResolveScaleButtonMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
ResolveScaleButtonMethod "getRequisition" o = Gtk.Widget.WidgetGetRequisitionMethodInfo
ResolveScaleButtonMethod "getResizeMode" o = Gtk.Container.ContainerGetResizeModeMethodInfo
ResolveScaleButtonMethod "getRootWindow" o = Gtk.Widget.WidgetGetRootWindowMethodInfo
ResolveScaleButtonMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
ResolveScaleButtonMethod "getScreen" o = Gtk.Widget.WidgetGetScreenMethodInfo
ResolveScaleButtonMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
ResolveScaleButtonMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
ResolveScaleButtonMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
ResolveScaleButtonMethod "getState" o = Gtk.Widget.WidgetGetStateMethodInfo
ResolveScaleButtonMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
ResolveScaleButtonMethod "getStyle" o = Gtk.Widget.WidgetGetStyleMethodInfo
ResolveScaleButtonMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
ResolveScaleButtonMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
ResolveScaleButtonMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
ResolveScaleButtonMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
ResolveScaleButtonMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
ResolveScaleButtonMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
ResolveScaleButtonMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
ResolveScaleButtonMethod "getUseActionAppearance" o = Gtk.Activatable.ActivatableGetUseActionAppearanceMethodInfo
ResolveScaleButtonMethod "getUseStock" o = Gtk.Button.ButtonGetUseStockMethodInfo
ResolveScaleButtonMethod "getUseUnderline" o = Gtk.Button.ButtonGetUseUnderlineMethodInfo
ResolveScaleButtonMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
ResolveScaleButtonMethod "getValignWithBaseline" o = Gtk.Widget.WidgetGetValignWithBaselineMethodInfo
ResolveScaleButtonMethod "getValue" o = ScaleButtonGetValueMethodInfo
ResolveScaleButtonMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
ResolveScaleButtonMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
ResolveScaleButtonMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
ResolveScaleButtonMethod "getVisual" o = Gtk.Widget.WidgetGetVisualMethodInfo
ResolveScaleButtonMethod "getWindow" o = Gtk.Widget.WidgetGetWindowMethodInfo
ResolveScaleButtonMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
ResolveScaleButtonMethod "setActionName" o = Gtk.Actionable.ActionableSetActionNameMethodInfo
ResolveScaleButtonMethod "setActionTargetValue" o = Gtk.Actionable.ActionableSetActionTargetValueMethodInfo
ResolveScaleButtonMethod "setAdjustment" o = ScaleButtonSetAdjustmentMethodInfo
ResolveScaleButtonMethod "setAlignment" o = Gtk.Button.ButtonSetAlignmentMethodInfo
ResolveScaleButtonMethod "setAllocation" o = Gtk.Widget.WidgetSetAllocationMethodInfo
ResolveScaleButtonMethod "setAlwaysShowImage" o = Gtk.Button.ButtonSetAlwaysShowImageMethodInfo
ResolveScaleButtonMethod "setAppPaintable" o = Gtk.Widget.WidgetSetAppPaintableMethodInfo
ResolveScaleButtonMethod "setBorderWidth" o = Gtk.Container.ContainerSetBorderWidthMethodInfo
ResolveScaleButtonMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
ResolveScaleButtonMethod "setCanDefault" o = Gtk.Widget.WidgetSetCanDefaultMethodInfo
ResolveScaleButtonMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
ResolveScaleButtonMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
ResolveScaleButtonMethod "setClip" o = Gtk.Widget.WidgetSetClipMethodInfo
ResolveScaleButtonMethod "setCompositeName" o = Gtk.Widget.WidgetSetCompositeNameMethodInfo
ResolveScaleButtonMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveScaleButtonMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveScaleButtonMethod "setDetailedActionName" o = Gtk.Actionable.ActionableSetDetailedActionNameMethodInfo
ResolveScaleButtonMethod "setDeviceEnabled" o = Gtk.Widget.WidgetSetDeviceEnabledMethodInfo
ResolveScaleButtonMethod "setDeviceEvents" o = Gtk.Widget.WidgetSetDeviceEventsMethodInfo
ResolveScaleButtonMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
ResolveScaleButtonMethod "setDoubleBuffered" o = Gtk.Widget.WidgetSetDoubleBufferedMethodInfo
ResolveScaleButtonMethod "setEvents" o = Gtk.Widget.WidgetSetEventsMethodInfo
ResolveScaleButtonMethod "setFocusChain" o = Gtk.Container.ContainerSetFocusChainMethodInfo
ResolveScaleButtonMethod "setFocusChild" o = Gtk.Container.ContainerSetFocusChildMethodInfo
ResolveScaleButtonMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
ResolveScaleButtonMethod "setFocusOnClick" o = Gtk.Button.ButtonSetFocusOnClickMethodInfo
ResolveScaleButtonMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
ResolveScaleButtonMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
ResolveScaleButtonMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
ResolveScaleButtonMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
ResolveScaleButtonMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
ResolveScaleButtonMethod "setHasWindow" o = Gtk.Widget.WidgetSetHasWindowMethodInfo
ResolveScaleButtonMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
ResolveScaleButtonMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
ResolveScaleButtonMethod "setIcons" o = ScaleButtonSetIconsMethodInfo
ResolveScaleButtonMethod "setImage" o = Gtk.Button.ButtonSetImageMethodInfo
ResolveScaleButtonMethod "setImagePosition" o = Gtk.Button.ButtonSetImagePositionMethodInfo
ResolveScaleButtonMethod "setLabel" o = Gtk.Button.ButtonSetLabelMethodInfo
ResolveScaleButtonMethod "setMapped" o = Gtk.Widget.WidgetSetMappedMethodInfo
ResolveScaleButtonMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
ResolveScaleButtonMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
ResolveScaleButtonMethod "setMarginLeft" o = Gtk.Widget.WidgetSetMarginLeftMethodInfo
ResolveScaleButtonMethod "setMarginRight" o = Gtk.Widget.WidgetSetMarginRightMethodInfo
ResolveScaleButtonMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
ResolveScaleButtonMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
ResolveScaleButtonMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
ResolveScaleButtonMethod "setNoShowAll" o = Gtk.Widget.WidgetSetNoShowAllMethodInfo
ResolveScaleButtonMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
ResolveScaleButtonMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
ResolveScaleButtonMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
ResolveScaleButtonMethod "setParentWindow" o = Gtk.Widget.WidgetSetParentWindowMethodInfo
ResolveScaleButtonMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveScaleButtonMethod "setRealized" o = Gtk.Widget.WidgetSetRealizedMethodInfo
ResolveScaleButtonMethod "setReallocateRedraws" o = Gtk.Container.ContainerSetReallocateRedrawsMethodInfo
ResolveScaleButtonMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
ResolveScaleButtonMethod "setRedrawOnAllocate" o = Gtk.Widget.WidgetSetRedrawOnAllocateMethodInfo
ResolveScaleButtonMethod "setRelatedAction" o = Gtk.Activatable.ActivatableSetRelatedActionMethodInfo
ResolveScaleButtonMethod "setRelief" o = Gtk.Button.ButtonSetReliefMethodInfo
ResolveScaleButtonMethod "setResizeMode" o = Gtk.Container.ContainerSetResizeModeMethodInfo
ResolveScaleButtonMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
ResolveScaleButtonMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
ResolveScaleButtonMethod "setState" o = Gtk.Widget.WidgetSetStateMethodInfo
ResolveScaleButtonMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
ResolveScaleButtonMethod "setStyle" o = Gtk.Widget.WidgetSetStyleMethodInfo
ResolveScaleButtonMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
ResolveScaleButtonMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
ResolveScaleButtonMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
ResolveScaleButtonMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
ResolveScaleButtonMethod "setUseActionAppearance" o = Gtk.Activatable.ActivatableSetUseActionAppearanceMethodInfo
ResolveScaleButtonMethod "setUseStock" o = Gtk.Button.ButtonSetUseStockMethodInfo
ResolveScaleButtonMethod "setUseUnderline" o = Gtk.Button.ButtonSetUseUnderlineMethodInfo
ResolveScaleButtonMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
ResolveScaleButtonMethod "setValue" o = ScaleButtonSetValueMethodInfo
ResolveScaleButtonMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
ResolveScaleButtonMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
ResolveScaleButtonMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
ResolveScaleButtonMethod "setVisual" o = Gtk.Widget.WidgetSetVisualMethodInfo
ResolveScaleButtonMethod "setWindow" o = Gtk.Widget.WidgetSetWindowMethodInfo
ResolveScaleButtonMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveScaleButtonMethod t ScaleButton, O.OverloadedMethod info ScaleButton p) => OL.IsLabel t (ScaleButton -> 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 ~ ResolveScaleButtonMethod t ScaleButton, O.OverloadedMethod info ScaleButton p, R.HasField t ScaleButton p) => R.HasField t ScaleButton p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveScaleButtonMethod t ScaleButton, O.OverloadedMethodInfo info ScaleButton) => OL.IsLabel t (O.MethodProxy info ScaleButton) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type ScaleButtonPopdownCallback =
IO ()
type C_ScaleButtonPopdownCallback =
Ptr ScaleButton ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ScaleButtonPopdownCallback :: C_ScaleButtonPopdownCallback -> IO (FunPtr C_ScaleButtonPopdownCallback)
wrap_ScaleButtonPopdownCallback ::
GObject a => (a -> ScaleButtonPopdownCallback) ->
C_ScaleButtonPopdownCallback
wrap_ScaleButtonPopdownCallback :: forall a. GObject a => (a -> IO ()) -> C_ScaleButtonPopdownCallback
wrap_ScaleButtonPopdownCallback a -> IO ()
gi'cb Ptr ScaleButton
gi'selfPtr Ptr ()
_ = do
Ptr ScaleButton -> (ScaleButton -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr ScaleButton
gi'selfPtr ((ScaleButton -> IO ()) -> IO ())
-> (ScaleButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ScaleButton
gi'self -> a -> IO ()
gi'cb (ScaleButton -> a
forall a b. Coercible a b => a -> b
Coerce.coerce ScaleButton
gi'self)
onScaleButtonPopdown :: (IsScaleButton a, MonadIO m) => a -> ((?self :: a) => ScaleButtonPopdownCallback) -> m SignalHandlerId
onScaleButtonPopdown :: forall a (m :: * -> *).
(IsScaleButton a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onScaleButtonPopdown a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_ScaleButtonPopdownCallback
wrapped' = (a -> IO ()) -> C_ScaleButtonPopdownCallback
forall a. GObject a => (a -> IO ()) -> C_ScaleButtonPopdownCallback
wrap_ScaleButtonPopdownCallback a -> IO ()
wrapped
FunPtr C_ScaleButtonPopdownCallback
wrapped'' <- C_ScaleButtonPopdownCallback
-> IO (FunPtr C_ScaleButtonPopdownCallback)
mk_ScaleButtonPopdownCallback C_ScaleButtonPopdownCallback
wrapped'
a
-> Text
-> FunPtr C_ScaleButtonPopdownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"popdown" FunPtr C_ScaleButtonPopdownCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterScaleButtonPopdown :: (IsScaleButton a, MonadIO m) => a -> ((?self :: a) => ScaleButtonPopdownCallback) -> m SignalHandlerId
afterScaleButtonPopdown :: forall a (m :: * -> *).
(IsScaleButton a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterScaleButtonPopdown a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_ScaleButtonPopdownCallback
wrapped' = (a -> IO ()) -> C_ScaleButtonPopdownCallback
forall a. GObject a => (a -> IO ()) -> C_ScaleButtonPopdownCallback
wrap_ScaleButtonPopdownCallback a -> IO ()
wrapped
FunPtr C_ScaleButtonPopdownCallback
wrapped'' <- C_ScaleButtonPopdownCallback
-> IO (FunPtr C_ScaleButtonPopdownCallback)
mk_ScaleButtonPopdownCallback C_ScaleButtonPopdownCallback
wrapped'
a
-> Text
-> FunPtr C_ScaleButtonPopdownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"popdown" FunPtr C_ScaleButtonPopdownCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ScaleButtonPopdownSignalInfo
instance SignalInfo ScaleButtonPopdownSignalInfo where
type HaskellCallbackType ScaleButtonPopdownSignalInfo = ScaleButtonPopdownCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ScaleButtonPopdownCallback cb
cb'' <- mk_ScaleButtonPopdownCallback cb'
connectSignalFunPtr obj "popdown" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton::popdown"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#g:signal:popdown"})
#endif
type =
IO ()
type =
Ptr ScaleButton ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
:: C_ScaleButtonPopupCallback -> IO (FunPtr C_ScaleButtonPopupCallback)
wrap_ScaleButtonPopupCallback ::
GObject a => (a -> ScaleButtonPopupCallback) ->
C_ScaleButtonPopupCallback
a -> IO ()
gi'cb Ptr ScaleButton
gi'selfPtr Ptr ()
_ = do
Ptr ScaleButton -> (ScaleButton -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr ScaleButton
gi'selfPtr ((ScaleButton -> IO ()) -> IO ())
-> (ScaleButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ScaleButton
gi'self -> a -> IO ()
gi'cb (ScaleButton -> a
forall a b. Coercible a b => a -> b
Coerce.coerce ScaleButton
gi'self)
onScaleButtonPopup :: (IsScaleButton a, MonadIO m) => a -> ((?self :: a) => ScaleButtonPopupCallback) -> m SignalHandlerId
a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_ScaleButtonPopdownCallback
wrapped' = (a -> IO ()) -> C_ScaleButtonPopdownCallback
forall a. GObject a => (a -> IO ()) -> C_ScaleButtonPopdownCallback
wrap_ScaleButtonPopupCallback a -> IO ()
wrapped
FunPtr C_ScaleButtonPopdownCallback
wrapped'' <- C_ScaleButtonPopdownCallback
-> IO (FunPtr C_ScaleButtonPopdownCallback)
mk_ScaleButtonPopupCallback C_ScaleButtonPopdownCallback
wrapped'
a
-> Text
-> FunPtr C_ScaleButtonPopdownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"popup" FunPtr C_ScaleButtonPopdownCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterScaleButtonPopup :: (IsScaleButton a, MonadIO m) => a -> ((?self :: a) => ScaleButtonPopupCallback) -> m SignalHandlerId
a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_ScaleButtonPopdownCallback
wrapped' = (a -> IO ()) -> C_ScaleButtonPopdownCallback
forall a. GObject a => (a -> IO ()) -> C_ScaleButtonPopdownCallback
wrap_ScaleButtonPopupCallback a -> IO ()
wrapped
FunPtr C_ScaleButtonPopdownCallback
wrapped'' <- C_ScaleButtonPopdownCallback
-> IO (FunPtr C_ScaleButtonPopdownCallback)
mk_ScaleButtonPopupCallback C_ScaleButtonPopdownCallback
wrapped'
a
-> Text
-> FunPtr C_ScaleButtonPopdownCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"popup" FunPtr C_ScaleButtonPopdownCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ScaleButtonPopupSignalInfo
instance SignalInfo ScaleButtonPopupSignalInfo where
type HaskellCallbackType ScaleButtonPopupSignalInfo = ScaleButtonPopupCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ScaleButtonPopupCallback cb
cb'' <- mk_ScaleButtonPopupCallback cb'
connectSignalFunPtr obj "popup" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton::popup"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#g:signal:popup"})
#endif
type ScaleButtonValueChangedCallback =
Double
-> IO ()
type C_ScaleButtonValueChangedCallback =
Ptr ScaleButton ->
CDouble ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ScaleButtonValueChangedCallback :: C_ScaleButtonValueChangedCallback -> IO (FunPtr C_ScaleButtonValueChangedCallback)
wrap_ScaleButtonValueChangedCallback ::
GObject a => (a -> ScaleButtonValueChangedCallback) ->
C_ScaleButtonValueChangedCallback
wrap_ScaleButtonValueChangedCallback :: forall a.
GObject a =>
(a -> ScaleButtonValueChangedCallback)
-> C_ScaleButtonValueChangedCallback
wrap_ScaleButtonValueChangedCallback a -> ScaleButtonValueChangedCallback
gi'cb Ptr ScaleButton
gi'selfPtr CDouble
value Ptr ()
_ = do
let value' :: Double
value' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
value
Ptr ScaleButton -> (ScaleButton -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr ScaleButton
gi'selfPtr ((ScaleButton -> IO ()) -> IO ())
-> (ScaleButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ScaleButton
gi'self -> a -> ScaleButtonValueChangedCallback
gi'cb (ScaleButton -> a
forall a b. Coercible a b => a -> b
Coerce.coerce ScaleButton
gi'self) Double
value'
onScaleButtonValueChanged :: (IsScaleButton a, MonadIO m) => a -> ((?self :: a) => ScaleButtonValueChangedCallback) -> m SignalHandlerId
onScaleButtonValueChanged :: forall a (m :: * -> *).
(IsScaleButton a, MonadIO m) =>
a
-> ((?self::a) => ScaleButtonValueChangedCallback)
-> m SignalHandlerId
onScaleButtonValueChanged a
obj (?self::a) => ScaleButtonValueChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> ScaleButtonValueChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ScaleButtonValueChangedCallback
ScaleButtonValueChangedCallback
cb
let wrapped' :: C_ScaleButtonValueChangedCallback
wrapped' = (a -> ScaleButtonValueChangedCallback)
-> C_ScaleButtonValueChangedCallback
forall a.
GObject a =>
(a -> ScaleButtonValueChangedCallback)
-> C_ScaleButtonValueChangedCallback
wrap_ScaleButtonValueChangedCallback a -> ScaleButtonValueChangedCallback
wrapped
FunPtr C_ScaleButtonValueChangedCallback
wrapped'' <- C_ScaleButtonValueChangedCallback
-> IO (FunPtr C_ScaleButtonValueChangedCallback)
mk_ScaleButtonValueChangedCallback C_ScaleButtonValueChangedCallback
wrapped'
a
-> Text
-> FunPtr C_ScaleButtonValueChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"value-changed" FunPtr C_ScaleButtonValueChangedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterScaleButtonValueChanged :: (IsScaleButton a, MonadIO m) => a -> ((?self :: a) => ScaleButtonValueChangedCallback) -> m SignalHandlerId
afterScaleButtonValueChanged :: forall a (m :: * -> *).
(IsScaleButton a, MonadIO m) =>
a
-> ((?self::a) => ScaleButtonValueChangedCallback)
-> m SignalHandlerId
afterScaleButtonValueChanged a
obj (?self::a) => ScaleButtonValueChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> ScaleButtonValueChangedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ScaleButtonValueChangedCallback
ScaleButtonValueChangedCallback
cb
let wrapped' :: C_ScaleButtonValueChangedCallback
wrapped' = (a -> ScaleButtonValueChangedCallback)
-> C_ScaleButtonValueChangedCallback
forall a.
GObject a =>
(a -> ScaleButtonValueChangedCallback)
-> C_ScaleButtonValueChangedCallback
wrap_ScaleButtonValueChangedCallback a -> ScaleButtonValueChangedCallback
wrapped
FunPtr C_ScaleButtonValueChangedCallback
wrapped'' <- C_ScaleButtonValueChangedCallback
-> IO (FunPtr C_ScaleButtonValueChangedCallback)
mk_ScaleButtonValueChangedCallback C_ScaleButtonValueChangedCallback
wrapped'
a
-> Text
-> FunPtr C_ScaleButtonValueChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"value-changed" FunPtr C_ScaleButtonValueChangedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ScaleButtonValueChangedSignalInfo
instance SignalInfo ScaleButtonValueChangedSignalInfo where
type HaskellCallbackType ScaleButtonValueChangedSignalInfo = ScaleButtonValueChangedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ScaleButtonValueChangedCallback cb
cb'' <- mk_ScaleButtonValueChangedCallback cb'
connectSignalFunPtr obj "value-changed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton::value-changed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#g:signal:valueChanged"})
#endif
getScaleButtonAdjustment :: (MonadIO m, IsScaleButton o) => o -> m Gtk.Adjustment.Adjustment
getScaleButtonAdjustment :: forall (m :: * -> *) o.
(MonadIO m, IsScaleButton o) =>
o -> m Adjustment
getScaleButtonAdjustment o
obj = IO Adjustment -> m Adjustment
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Adjustment -> m Adjustment) -> IO Adjustment -> m Adjustment
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Adjustment) -> IO Adjustment
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getScaleButtonAdjustment" (IO (Maybe Adjustment) -> IO Adjustment)
-> IO (Maybe Adjustment) -> IO Adjustment
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Adjustment -> Adjustment)
-> IO (Maybe Adjustment)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"adjustment" ManagedPtr Adjustment -> Adjustment
Gtk.Adjustment.Adjustment
setScaleButtonAdjustment :: (MonadIO m, IsScaleButton o, Gtk.Adjustment.IsAdjustment a) => o -> a -> m ()
setScaleButtonAdjustment :: forall (m :: * -> *) o a.
(MonadIO m, IsScaleButton o, IsAdjustment a) =>
o -> a -> m ()
setScaleButtonAdjustment o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"adjustment" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructScaleButtonAdjustment :: (IsScaleButton o, MIO.MonadIO m, Gtk.Adjustment.IsAdjustment a) => a -> m (GValueConstruct o)
constructScaleButtonAdjustment :: forall o (m :: * -> *) a.
(IsScaleButton o, MonadIO m, IsAdjustment a) =>
a -> m (GValueConstruct o)
constructScaleButtonAdjustment a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"adjustment" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data ScaleButtonAdjustmentPropertyInfo
instance AttrInfo ScaleButtonAdjustmentPropertyInfo where
type AttrAllowedOps ScaleButtonAdjustmentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ScaleButtonAdjustmentPropertyInfo = IsScaleButton
type AttrSetTypeConstraint ScaleButtonAdjustmentPropertyInfo = Gtk.Adjustment.IsAdjustment
type AttrTransferTypeConstraint ScaleButtonAdjustmentPropertyInfo = Gtk.Adjustment.IsAdjustment
type AttrTransferType ScaleButtonAdjustmentPropertyInfo = Gtk.Adjustment.Adjustment
type AttrGetType ScaleButtonAdjustmentPropertyInfo = Gtk.Adjustment.Adjustment
type AttrLabel ScaleButtonAdjustmentPropertyInfo = "adjustment"
type AttrOrigin ScaleButtonAdjustmentPropertyInfo = ScaleButton
attrGet = getScaleButtonAdjustment
attrSet = setScaleButtonAdjustment
attrTransfer _ v = do
unsafeCastTo Gtk.Adjustment.Adjustment v
attrConstruct = constructScaleButtonAdjustment
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.adjustment"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#g:attr:adjustment"
})
#endif
getScaleButtonIcons :: (MonadIO m, IsScaleButton o) => o -> m (Maybe [T.Text])
getScaleButtonIcons :: forall (m :: * -> *) o.
(MonadIO m, IsScaleButton o) =>
o -> m (Maybe [Text])
getScaleButtonIcons o
obj = IO (Maybe [Text]) -> m (Maybe [Text])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe [Text])
forall a. GObject a => a -> String -> IO (Maybe [Text])
B.Properties.getObjectPropertyStringArray o
obj String
"icons"
setScaleButtonIcons :: (MonadIO m, IsScaleButton o) => o -> [T.Text] -> m ()
setScaleButtonIcons :: forall (m :: * -> *) o.
(MonadIO m, IsScaleButton o) =>
o -> [Text] -> m ()
setScaleButtonIcons o
obj [Text]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe [Text] -> IO ()
forall a. GObject a => a -> String -> Maybe [Text] -> IO ()
B.Properties.setObjectPropertyStringArray o
obj String
"icons" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
constructScaleButtonIcons :: (IsScaleButton o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructScaleButtonIcons :: forall o (m :: * -> *).
(IsScaleButton o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructScaleButtonIcons [Text]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray String
"icons" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
#if defined(ENABLE_OVERLOADING)
data ScaleButtonIconsPropertyInfo
instance AttrInfo ScaleButtonIconsPropertyInfo where
type AttrAllowedOps ScaleButtonIconsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ScaleButtonIconsPropertyInfo = IsScaleButton
type AttrSetTypeConstraint ScaleButtonIconsPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint ScaleButtonIconsPropertyInfo = (~) [T.Text]
type AttrTransferType ScaleButtonIconsPropertyInfo = [T.Text]
type AttrGetType ScaleButtonIconsPropertyInfo = (Maybe [T.Text])
type AttrLabel ScaleButtonIconsPropertyInfo = "icons"
type AttrOrigin ScaleButtonIconsPropertyInfo = ScaleButton
attrGet = getScaleButtonIcons
attrSet = setScaleButtonIcons
attrTransfer _ v = do
return v
attrConstruct = constructScaleButtonIcons
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.icons"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#g:attr:icons"
})
#endif
getScaleButtonSize :: (MonadIO m, IsScaleButton o) => o -> m Gtk.Enums.IconSize
getScaleButtonSize :: forall (m :: * -> *) o.
(MonadIO m, IsScaleButton o) =>
o -> m IconSize
getScaleButtonSize o
obj = IO IconSize -> m IconSize
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO IconSize -> m IconSize) -> IO IconSize -> m IconSize
forall a b. (a -> b) -> a -> b
$ o -> String -> IO IconSize
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"size"
setScaleButtonSize :: (MonadIO m, IsScaleButton o) => o -> Gtk.Enums.IconSize -> m ()
setScaleButtonSize :: forall (m :: * -> *) o.
(MonadIO m, IsScaleButton o) =>
o -> IconSize -> m ()
setScaleButtonSize o
obj IconSize
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 -> IconSize -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"size" IconSize
val
constructScaleButtonSize :: (IsScaleButton o, MIO.MonadIO m) => Gtk.Enums.IconSize -> m (GValueConstruct o)
constructScaleButtonSize :: forall o (m :: * -> *).
(IsScaleButton o, MonadIO m) =>
IconSize -> m (GValueConstruct o)
constructScaleButtonSize IconSize
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 -> IconSize -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"size" IconSize
val
#if defined(ENABLE_OVERLOADING)
data ScaleButtonSizePropertyInfo
instance AttrInfo ScaleButtonSizePropertyInfo where
type AttrAllowedOps ScaleButtonSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ScaleButtonSizePropertyInfo = IsScaleButton
type AttrSetTypeConstraint ScaleButtonSizePropertyInfo = (~) Gtk.Enums.IconSize
type AttrTransferTypeConstraint ScaleButtonSizePropertyInfo = (~) Gtk.Enums.IconSize
type AttrTransferType ScaleButtonSizePropertyInfo = Gtk.Enums.IconSize
type AttrGetType ScaleButtonSizePropertyInfo = Gtk.Enums.IconSize
type AttrLabel ScaleButtonSizePropertyInfo = "size"
type AttrOrigin ScaleButtonSizePropertyInfo = ScaleButton
attrGet = getScaleButtonSize
attrSet = setScaleButtonSize
attrTransfer _ v = do
return v
attrConstruct = constructScaleButtonSize
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.size"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#g:attr:size"
})
#endif
getScaleButtonValue :: (MonadIO m, IsScaleButton o) => o -> m Double
getScaleButtonValue :: forall (m :: * -> *) o.
(MonadIO m, IsScaleButton o) =>
o -> m Double
getScaleButtonValue o
obj = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Double
forall a. GObject a => a -> String -> IO Double
B.Properties.getObjectPropertyDouble o
obj String
"value"
setScaleButtonValue :: (MonadIO m, IsScaleButton o) => o -> Double -> m ()
setScaleButtonValue :: forall (m :: * -> *) o.
(MonadIO m, IsScaleButton o) =>
o -> Double -> m ()
setScaleButtonValue o
obj Double
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 -> ScaleButtonValueChangedCallback
forall a.
GObject a =>
a -> String -> ScaleButtonValueChangedCallback
B.Properties.setObjectPropertyDouble o
obj String
"value" Double
val
constructScaleButtonValue :: (IsScaleButton o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructScaleButtonValue :: forall o (m :: * -> *).
(IsScaleButton o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructScaleButtonValue Double
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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"value" Double
val
#if defined(ENABLE_OVERLOADING)
data ScaleButtonValuePropertyInfo
instance AttrInfo ScaleButtonValuePropertyInfo where
type AttrAllowedOps ScaleButtonValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ScaleButtonValuePropertyInfo = IsScaleButton
type AttrSetTypeConstraint ScaleButtonValuePropertyInfo = (~) Double
type AttrTransferTypeConstraint ScaleButtonValuePropertyInfo = (~) Double
type AttrTransferType ScaleButtonValuePropertyInfo = Double
type AttrGetType ScaleButtonValuePropertyInfo = Double
type AttrLabel ScaleButtonValuePropertyInfo = "value"
type AttrOrigin ScaleButtonValuePropertyInfo = ScaleButton
attrGet = getScaleButtonValue
attrSet = setScaleButtonValue
attrTransfer _ v = do
return v
attrConstruct = constructScaleButtonValue
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.value"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#g:attr:value"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ScaleButton
type instance O.AttributeList ScaleButton = ScaleButtonAttributeList
type ScaleButtonAttributeList = ('[ '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("adjustment", ScaleButtonAdjustmentPropertyInfo), '("alwaysShowImage", Gtk.Button.ButtonAlwaysShowImagePropertyInfo), '("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), '("icons", ScaleButtonIconsPropertyInfo), '("image", Gtk.Button.ButtonImagePropertyInfo), '("imagePosition", Gtk.Button.ButtonImagePositionPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("label", Gtk.Button.ButtonLabelPropertyInfo), '("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), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("relatedAction", Gtk.Activatable.ActivatableRelatedActionPropertyInfo), '("relief", Gtk.Button.ButtonReliefPropertyInfo), '("resizeMode", Gtk.Container.ContainerResizeModePropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("size", ScaleButtonSizePropertyInfo), '("style", Gtk.Widget.WidgetStylePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useActionAppearance", Gtk.Activatable.ActivatableUseActionAppearancePropertyInfo), '("useStock", Gtk.Button.ButtonUseStockPropertyInfo), '("useUnderline", Gtk.Button.ButtonUseUnderlinePropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("value", ScaleButtonValuePropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("window", Gtk.Widget.WidgetWindowPropertyInfo), '("xalign", Gtk.Button.ButtonXalignPropertyInfo), '("yalign", Gtk.Button.ButtonYalignPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
scaleButtonAdjustment :: AttrLabelProxy "adjustment"
scaleButtonAdjustment = AttrLabelProxy
scaleButtonIcons :: AttrLabelProxy "icons"
scaleButtonIcons = AttrLabelProxy
scaleButtonSize :: AttrLabelProxy "size"
scaleButtonSize = AttrLabelProxy
scaleButtonValue :: AttrLabelProxy "value"
scaleButtonValue = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ScaleButton = ScaleButtonSignalList
type ScaleButtonSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("activate", Gtk.Button.ButtonActivateSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("buttonPressEvent", Gtk.Widget.WidgetButtonPressEventSignalInfo), '("buttonReleaseEvent", Gtk.Widget.WidgetButtonReleaseEventSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("checkResize", Gtk.Container.ContainerCheckResizeSignalInfo), '("childNotify", Gtk.Widget.WidgetChildNotifySignalInfo), '("clicked", Gtk.Button.ButtonClickedSignalInfo), '("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), '("enter", Gtk.Button.ButtonEnterSignalInfo), '("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), '("leave", Gtk.Button.ButtonLeaveSignalInfo), '("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), '("popdown", ScaleButtonPopdownSignalInfo), '("popup", ScaleButtonPopupSignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("pressed", Gtk.Button.ButtonPressedSignalInfo), '("propertyNotifyEvent", Gtk.Widget.WidgetPropertyNotifyEventSignalInfo), '("proximityInEvent", Gtk.Widget.WidgetProximityInEventSignalInfo), '("proximityOutEvent", Gtk.Widget.WidgetProximityOutEventSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("released", Gtk.Button.ButtonReleasedSignalInfo), '("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), '("valueChanged", ScaleButtonValueChangedSignalInfo), '("visibilityNotifyEvent", Gtk.Widget.WidgetVisibilityNotifyEventSignalInfo), '("windowStateEvent", Gtk.Widget.WidgetWindowStateEventSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_scale_button_new" gtk_scale_button_new ::
Int32 ->
CDouble ->
CDouble ->
CDouble ->
Ptr CString ->
IO (Ptr ScaleButton)
scaleButtonNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Int32
-> Double
-> Double
-> Double
-> Maybe ([T.Text])
-> m ScaleButton
scaleButtonNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Int32
-> Double -> Double -> Double -> Maybe [Text] -> m ScaleButton
scaleButtonNew Int32
size Double
min Double
max Double
step Maybe [Text]
icons = IO ScaleButton -> m ScaleButton
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ScaleButton -> m ScaleButton)
-> IO ScaleButton -> m ScaleButton
forall a b. (a -> b) -> a -> b
$ do
let min' :: CDouble
min' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
min
let max' :: CDouble
max' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
max
let step' :: CDouble
step' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
step
Ptr CString
maybeIcons <- case Maybe [Text]
icons of
Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
Just [Text]
jIcons -> do
Ptr CString
jIcons' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jIcons
Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jIcons'
Ptr ScaleButton
result <- Int32
-> CDouble
-> CDouble
-> CDouble
-> Ptr CString
-> IO (Ptr ScaleButton)
gtk_scale_button_new Int32
size CDouble
min' CDouble
max' CDouble
step' Ptr CString
maybeIcons
Text -> Ptr ScaleButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"scaleButtonNew" Ptr ScaleButton
result
ScaleButton
result' <- ((ManagedPtr ScaleButton -> ScaleButton)
-> Ptr ScaleButton -> IO ScaleButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ScaleButton -> ScaleButton
ScaleButton) Ptr ScaleButton
result
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeIcons
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeIcons
ScaleButton -> IO ScaleButton
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ScaleButton
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_scale_button_get_adjustment" gtk_scale_button_get_adjustment ::
Ptr ScaleButton ->
IO (Ptr Gtk.Adjustment.Adjustment)
scaleButtonGetAdjustment ::
(B.CallStack.HasCallStack, MonadIO m, IsScaleButton a) =>
a
-> m Gtk.Adjustment.Adjustment
scaleButtonGetAdjustment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsScaleButton a) =>
a -> m Adjustment
scaleButtonGetAdjustment a
button = IO Adjustment -> m Adjustment
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Adjustment -> m Adjustment) -> IO Adjustment -> m Adjustment
forall a b. (a -> b) -> a -> b
$ do
Ptr ScaleButton
button' <- a -> IO (Ptr ScaleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
Ptr Adjustment
result <- Ptr ScaleButton -> IO (Ptr Adjustment)
gtk_scale_button_get_adjustment Ptr ScaleButton
button'
Text -> Ptr Adjustment -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"scaleButtonGetAdjustment" Ptr Adjustment
result
Adjustment
result' <- ((ManagedPtr Adjustment -> Adjustment)
-> Ptr Adjustment -> IO Adjustment
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Adjustment -> Adjustment
Gtk.Adjustment.Adjustment) Ptr Adjustment
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
Adjustment -> IO Adjustment
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Adjustment
result'
#if defined(ENABLE_OVERLOADING)
data ScaleButtonGetAdjustmentMethodInfo
instance (signature ~ (m Gtk.Adjustment.Adjustment), MonadIO m, IsScaleButton a) => O.OverloadedMethod ScaleButtonGetAdjustmentMethodInfo a signature where
overloadedMethod = scaleButtonGetAdjustment
instance O.OverloadedMethodInfo ScaleButtonGetAdjustmentMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.scaleButtonGetAdjustment",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#v:scaleButtonGetAdjustment"
})
#endif
foreign import ccall "gtk_scale_button_get_minus_button" gtk_scale_button_get_minus_button ::
Ptr ScaleButton ->
IO (Ptr Gtk.Button.Button)
scaleButtonGetMinusButton ::
(B.CallStack.HasCallStack, MonadIO m, IsScaleButton a) =>
a
-> m Gtk.Button.Button
scaleButtonGetMinusButton :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsScaleButton a) =>
a -> m Button
scaleButtonGetMinusButton a
button = IO Button -> m Button
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Button -> m Button) -> IO Button -> m Button
forall a b. (a -> b) -> a -> b
$ do
Ptr ScaleButton
button' <- a -> IO (Ptr ScaleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
Ptr Button
result <- Ptr ScaleButton -> IO (Ptr Button)
gtk_scale_button_get_minus_button Ptr ScaleButton
button'
Text -> Ptr Button -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"scaleButtonGetMinusButton" Ptr Button
result
Button
result' <- ((ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Button -> Button
Gtk.Button.Button) Ptr Button
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
Button -> IO Button
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Button
result'
#if defined(ENABLE_OVERLOADING)
data ScaleButtonGetMinusButtonMethodInfo
instance (signature ~ (m Gtk.Button.Button), MonadIO m, IsScaleButton a) => O.OverloadedMethod ScaleButtonGetMinusButtonMethodInfo a signature where
overloadedMethod = scaleButtonGetMinusButton
instance O.OverloadedMethodInfo ScaleButtonGetMinusButtonMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.scaleButtonGetMinusButton",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#v:scaleButtonGetMinusButton"
})
#endif
foreign import ccall "gtk_scale_button_get_plus_button" gtk_scale_button_get_plus_button ::
Ptr ScaleButton ->
IO (Ptr Gtk.Button.Button)
scaleButtonGetPlusButton ::
(B.CallStack.HasCallStack, MonadIO m, IsScaleButton a) =>
a
-> m Gtk.Button.Button
scaleButtonGetPlusButton :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsScaleButton a) =>
a -> m Button
scaleButtonGetPlusButton a
button = IO Button -> m Button
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Button -> m Button) -> IO Button -> m Button
forall a b. (a -> b) -> a -> b
$ do
Ptr ScaleButton
button' <- a -> IO (Ptr ScaleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
Ptr Button
result <- Ptr ScaleButton -> IO (Ptr Button)
gtk_scale_button_get_plus_button Ptr ScaleButton
button'
Text -> Ptr Button -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"scaleButtonGetPlusButton" Ptr Button
result
Button
result' <- ((ManagedPtr Button -> Button) -> Ptr Button -> IO Button
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Button -> Button
Gtk.Button.Button) Ptr Button
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
Button -> IO Button
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Button
result'
#if defined(ENABLE_OVERLOADING)
data ScaleButtonGetPlusButtonMethodInfo
instance (signature ~ (m Gtk.Button.Button), MonadIO m, IsScaleButton a) => O.OverloadedMethod ScaleButtonGetPlusButtonMethodInfo a signature where
overloadedMethod = scaleButtonGetPlusButton
instance O.OverloadedMethodInfo ScaleButtonGetPlusButtonMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.scaleButtonGetPlusButton",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#v:scaleButtonGetPlusButton"
})
#endif
foreign import ccall "gtk_scale_button_get_popup" ::
Ptr ScaleButton ->
IO (Ptr Gtk.Widget.Widget)
scaleButtonGetPopup ::
(B.CallStack.HasCallStack, MonadIO m, IsScaleButton a) =>
a
-> m Gtk.Widget.Widget
a
button = IO Widget -> m Widget
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
Ptr ScaleButton
button' <- a -> IO (Ptr ScaleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
Ptr Widget
result <- Ptr ScaleButton -> IO (Ptr Widget)
gtk_scale_button_get_popup Ptr ScaleButton
button'
Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"scaleButtonGetPopup" Ptr Widget
result
Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
Widget -> IO Widget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'
#if defined(ENABLE_OVERLOADING)
data ScaleButtonGetPopupMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsScaleButton a) => O.OverloadedMethod ScaleButtonGetPopupMethodInfo a signature where
overloadedMethod = scaleButtonGetPopup
instance O.OverloadedMethodInfo ScaleButtonGetPopupMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.scaleButtonGetPopup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#v:scaleButtonGetPopup"
})
#endif
foreign import ccall "gtk_scale_button_get_value" gtk_scale_button_get_value ::
Ptr ScaleButton ->
IO CDouble
scaleButtonGetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsScaleButton a) =>
a
-> m Double
scaleButtonGetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsScaleButton a) =>
a -> m Double
scaleButtonGetValue a
button = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
Ptr ScaleButton
button' <- a -> IO (Ptr ScaleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
CDouble
result <- Ptr ScaleButton -> IO CDouble
gtk_scale_button_get_value Ptr ScaleButton
button'
let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'
#if defined(ENABLE_OVERLOADING)
data ScaleButtonGetValueMethodInfo
instance (signature ~ (m Double), MonadIO m, IsScaleButton a) => O.OverloadedMethod ScaleButtonGetValueMethodInfo a signature where
overloadedMethod = scaleButtonGetValue
instance O.OverloadedMethodInfo ScaleButtonGetValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.scaleButtonGetValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#v:scaleButtonGetValue"
})
#endif
foreign import ccall "gtk_scale_button_set_adjustment" gtk_scale_button_set_adjustment ::
Ptr ScaleButton ->
Ptr Gtk.Adjustment.Adjustment ->
IO ()
scaleButtonSetAdjustment ::
(B.CallStack.HasCallStack, MonadIO m, IsScaleButton a, Gtk.Adjustment.IsAdjustment b) =>
a
-> b
-> m ()
scaleButtonSetAdjustment :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsScaleButton a, IsAdjustment b) =>
a -> b -> m ()
scaleButtonSetAdjustment a
button b
adjustment = 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 ScaleButton
button' <- a -> IO (Ptr ScaleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
Ptr Adjustment
adjustment' <- b -> IO (Ptr Adjustment)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
adjustment
Ptr ScaleButton -> Ptr Adjustment -> IO ()
gtk_scale_button_set_adjustment Ptr ScaleButton
button' Ptr Adjustment
adjustment'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
adjustment
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ScaleButtonSetAdjustmentMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsScaleButton a, Gtk.Adjustment.IsAdjustment b) => O.OverloadedMethod ScaleButtonSetAdjustmentMethodInfo a signature where
overloadedMethod = scaleButtonSetAdjustment
instance O.OverloadedMethodInfo ScaleButtonSetAdjustmentMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.scaleButtonSetAdjustment",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#v:scaleButtonSetAdjustment"
})
#endif
foreign import ccall "gtk_scale_button_set_icons" gtk_scale_button_set_icons ::
Ptr ScaleButton ->
Ptr CString ->
IO ()
scaleButtonSetIcons ::
(B.CallStack.HasCallStack, MonadIO m, IsScaleButton a) =>
a
-> [T.Text]
-> m ()
scaleButtonSetIcons :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsScaleButton a) =>
a -> [Text] -> m ()
scaleButtonSetIcons a
button [Text]
icons = 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 ScaleButton
button' <- a -> IO (Ptr ScaleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
Ptr CString
icons' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
icons
Ptr ScaleButton -> Ptr CString -> IO ()
gtk_scale_button_set_icons Ptr ScaleButton
button' Ptr CString
icons'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
icons'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
icons'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ScaleButtonSetIconsMethodInfo
instance (signature ~ ([T.Text] -> m ()), MonadIO m, IsScaleButton a) => O.OverloadedMethod ScaleButtonSetIconsMethodInfo a signature where
overloadedMethod = scaleButtonSetIcons
instance O.OverloadedMethodInfo ScaleButtonSetIconsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.scaleButtonSetIcons",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#v:scaleButtonSetIcons"
})
#endif
foreign import ccall "gtk_scale_button_set_value" gtk_scale_button_set_value ::
Ptr ScaleButton ->
CDouble ->
IO ()
scaleButtonSetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsScaleButton a) =>
a
-> Double
-> m ()
scaleButtonSetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsScaleButton a) =>
a -> Double -> m ()
scaleButtonSetValue a
button Double
value = 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 ScaleButton
button' <- a -> IO (Ptr ScaleButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
button
let value' :: CDouble
value' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
value
Ptr ScaleButton -> CDouble -> IO ()
gtk_scale_button_set_value Ptr ScaleButton
button' CDouble
value'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
button
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ScaleButtonSetValueMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsScaleButton a) => O.OverloadedMethod ScaleButtonSetValueMethodInfo a signature where
overloadedMethod = scaleButtonSetValue
instance O.OverloadedMethodInfo ScaleButtonSetValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.ScaleButton.scaleButtonSetValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-ScaleButton.html#v:scaleButtonSetValue"
})
#endif