{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gtk.Objects.Scrollbar.Scrollbar' widget is a horizontal or vertical scrollbar,
-- depending on the value of the t'GI.Gtk.Interfaces.Orientable.Orientable':@/orientation/@ property.
-- 
-- Its position and movement are controlled by the adjustment that is passed to
-- or created by 'GI.Gtk.Objects.Scrollbar.scrollbarNew'. See t'GI.Gtk.Objects.Adjustment.Adjustment' for more details. The
-- t'GI.Gtk.Objects.Adjustment.Adjustment':@/value/@ field sets the position of the thumb and must be between
-- t'GI.Gtk.Objects.Adjustment.Adjustment':@/lower/@ and t'GI.Gtk.Objects.Adjustment.Adjustment':@/upper/@ - t'GI.Gtk.Objects.Adjustment.Adjustment':@/page-size/@. The
-- t'GI.Gtk.Objects.Adjustment.Adjustment':@/page-size/@ represents the size of the visible scrollable area.
-- The fields t'GI.Gtk.Objects.Adjustment.Adjustment':@/step-increment/@ and t'GI.Gtk.Objects.Adjustment.Adjustment':@/page-increment/@
-- fields are added to or subtracted from the t'GI.Gtk.Objects.Adjustment.Adjustment':@/value/@ when the user
-- asks to move by a step (using e.g. the cursor arrow keys or, if present, the
-- stepper buttons) or by a page (using e.g. the Page Down\/Up keys).
-- 
-- = CSS nodes
-- 
-- 
-- === /plain code/
-- >
-- >scrollbar
-- >╰── box
-- >    ╰── range[.fine-tune]
-- >        ╰── trough
-- >            ╰── slider
-- 
-- 
-- GtkScrollbar has a main CSS node with name scrollbar and a subnode for its
-- contents. Both the main node and the box subnode get the .horizontal or .vertical
-- style classes applied, depending on the scrollbar\'s orientation.
-- 
-- The range node gets the style class .fine-tune added when the scrollbar is
-- in \'fine-tuning\' mode.
-- 
-- If steppers are enabled, they are represented by up to four additional
-- subnodes with name button. These get the style classes .up and .down to
-- indicate in which direction they are moving.
-- 
-- Other style classes that may be added to scrollbars inside t'GI.Gtk.Objects.ScrolledWindow.ScrolledWindow'
-- include the positional classes (.left, .right, .top, .bottom) and style
-- classes related to overlay scrolling (.overlay-indicator, .dragging, .hovering).

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

module GI.Gtk.Objects.Scrollbar
    ( 

-- * Exported types
    Scrollbar(..)                           ,
    IsScrollbar                             ,
    toScrollbar                             ,
    noScrollbar                             ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveScrollbarMethod                  ,
#endif


-- ** getAdjustment #method:getAdjustment#

#if defined(ENABLE_OVERLOADING)
    ScrollbarGetAdjustmentMethodInfo        ,
#endif
    scrollbarGetAdjustment                  ,


-- ** new #method:new#

    scrollbarNew                            ,


-- ** setAdjustment #method:setAdjustment#

#if defined(ENABLE_OVERLOADING)
    ScrollbarSetAdjustmentMethodInfo        ,
#endif
    scrollbarSetAdjustment                  ,




 -- * Properties
-- ** adjustment #attr:adjustment#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ScrollbarAdjustmentPropertyInfo         ,
#endif
    clearScrollbarAdjustment                ,
    constructScrollbarAdjustment            ,
    getScrollbarAdjustment                  ,
#if defined(ENABLE_OVERLOADING)
    scrollbarAdjustment                     ,
#endif
    setScrollbarAdjustment                  ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.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.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.Widget as Gtk.Widget

-- | Memory-managed wrapper type.
newtype Scrollbar = Scrollbar (ManagedPtr Scrollbar)
    deriving (Scrollbar -> Scrollbar -> Bool
(Scrollbar -> Scrollbar -> Bool)
-> (Scrollbar -> Scrollbar -> Bool) -> Eq Scrollbar
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scrollbar -> Scrollbar -> Bool
$c/= :: Scrollbar -> Scrollbar -> Bool
== :: Scrollbar -> Scrollbar -> Bool
$c== :: Scrollbar -> Scrollbar -> Bool
Eq)
foreign import ccall "gtk_scrollbar_get_type"
    c_gtk_scrollbar_get_type :: IO GType

instance GObject Scrollbar where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_scrollbar_get_type
    

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

-- | Type class for types which can be safely cast to `Scrollbar`, for instance with `toScrollbar`.
class (GObject o, O.IsDescendantOf Scrollbar o) => IsScrollbar o
instance (GObject o, O.IsDescendantOf Scrollbar o) => IsScrollbar o

instance O.HasParentTypes Scrollbar
type instance O.ParentTypes Scrollbar = '[Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.Orientable.Orientable]

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

-- | A convenience alias for `Nothing` :: `Maybe` `Scrollbar`.
noScrollbar :: Maybe Scrollbar
noScrollbar :: Maybe Scrollbar
noScrollbar = Maybe Scrollbar
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveScrollbarMethod (t :: Symbol) (o :: *) :: * where
    ResolveScrollbarMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveScrollbarMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveScrollbarMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveScrollbarMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveScrollbarMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveScrollbarMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveScrollbarMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveScrollbarMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveScrollbarMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveScrollbarMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveScrollbarMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveScrollbarMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveScrollbarMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveScrollbarMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveScrollbarMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveScrollbarMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveScrollbarMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveScrollbarMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveScrollbarMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveScrollbarMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveScrollbarMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveScrollbarMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveScrollbarMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveScrollbarMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveScrollbarMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveScrollbarMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveScrollbarMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveScrollbarMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveScrollbarMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveScrollbarMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveScrollbarMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveScrollbarMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveScrollbarMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveScrollbarMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveScrollbarMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveScrollbarMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveScrollbarMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveScrollbarMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveScrollbarMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveScrollbarMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveScrollbarMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveScrollbarMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveScrollbarMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveScrollbarMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveScrollbarMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveScrollbarMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveScrollbarMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveScrollbarMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveScrollbarMethod "dragSourceSetIconPaintable" o = Gtk.Widget.WidgetDragSourceSetIconPaintableMethodInfo
    ResolveScrollbarMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveScrollbarMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveScrollbarMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveScrollbarMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveScrollbarMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveScrollbarMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveScrollbarMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveScrollbarMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveScrollbarMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveScrollbarMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveScrollbarMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveScrollbarMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveScrollbarMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveScrollbarMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveScrollbarMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveScrollbarMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveScrollbarMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveScrollbarMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveScrollbarMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveScrollbarMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveScrollbarMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveScrollbarMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveScrollbarMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveScrollbarMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveScrollbarMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveScrollbarMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveScrollbarMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveScrollbarMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveScrollbarMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveScrollbarMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveScrollbarMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveScrollbarMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveScrollbarMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveScrollbarMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveScrollbarMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveScrollbarMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveScrollbarMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveScrollbarMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveScrollbarMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveScrollbarMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveScrollbarMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveScrollbarMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveScrollbarMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveScrollbarMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveScrollbarMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveScrollbarMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveScrollbarMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveScrollbarMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveScrollbarMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveScrollbarMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveScrollbarMethod "registerSurface" o = Gtk.Widget.WidgetRegisterSurfaceMethodInfo
    ResolveScrollbarMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveScrollbarMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveScrollbarMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveScrollbarMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveScrollbarMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveScrollbarMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveScrollbarMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveScrollbarMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveScrollbarMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveScrollbarMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveScrollbarMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveScrollbarMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveScrollbarMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveScrollbarMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveScrollbarMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveScrollbarMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveScrollbarMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveScrollbarMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveScrollbarMethod "unregisterSurface" o = Gtk.Widget.WidgetUnregisterSurfaceMethodInfo
    ResolveScrollbarMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveScrollbarMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveScrollbarMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveScrollbarMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveScrollbarMethod "getAdjustment" o = ScrollbarGetAdjustmentMethodInfo
    ResolveScrollbarMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveScrollbarMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveScrollbarMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveScrollbarMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveScrollbarMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveScrollbarMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveScrollbarMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveScrollbarMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveScrollbarMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveScrollbarMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveScrollbarMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveScrollbarMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveScrollbarMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveScrollbarMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveScrollbarMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveScrollbarMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveScrollbarMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveScrollbarMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveScrollbarMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveScrollbarMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveScrollbarMethod "getHasSurface" o = Gtk.Widget.WidgetGetHasSurfaceMethodInfo
    ResolveScrollbarMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveScrollbarMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveScrollbarMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveScrollbarMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveScrollbarMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveScrollbarMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveScrollbarMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveScrollbarMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveScrollbarMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveScrollbarMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveScrollbarMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveScrollbarMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveScrollbarMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveScrollbarMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveScrollbarMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveScrollbarMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveScrollbarMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveScrollbarMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveScrollbarMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveScrollbarMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveScrollbarMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveScrollbarMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveScrollbarMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveScrollbarMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveScrollbarMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveScrollbarMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveScrollbarMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveScrollbarMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveScrollbarMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveScrollbarMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveScrollbarMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveScrollbarMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveScrollbarMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveScrollbarMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveScrollbarMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveScrollbarMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveScrollbarMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveScrollbarMethod "getSurface" o = Gtk.Widget.WidgetGetSurfaceMethodInfo
    ResolveScrollbarMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveScrollbarMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveScrollbarMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveScrollbarMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveScrollbarMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveScrollbarMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveScrollbarMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveScrollbarMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveScrollbarMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveScrollbarMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveScrollbarMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveScrollbarMethod "setAdjustment" o = ScrollbarSetAdjustmentMethodInfo
    ResolveScrollbarMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveScrollbarMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveScrollbarMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveScrollbarMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveScrollbarMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveScrollbarMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveScrollbarMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveScrollbarMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveScrollbarMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveScrollbarMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveScrollbarMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveScrollbarMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveScrollbarMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveScrollbarMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveScrollbarMethod "setHasSurface" o = Gtk.Widget.WidgetSetHasSurfaceMethodInfo
    ResolveScrollbarMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveScrollbarMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveScrollbarMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveScrollbarMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveScrollbarMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveScrollbarMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveScrollbarMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveScrollbarMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveScrollbarMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveScrollbarMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveScrollbarMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveScrollbarMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveScrollbarMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveScrollbarMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveScrollbarMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveScrollbarMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveScrollbarMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveScrollbarMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveScrollbarMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveScrollbarMethod "setSurface" o = Gtk.Widget.WidgetSetSurfaceMethodInfo
    ResolveScrollbarMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveScrollbarMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveScrollbarMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveScrollbarMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveScrollbarMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveScrollbarMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveScrollbarMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveScrollbarMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "adjustment"
   -- Type: TInterface (Name {namespace = "Gtk", name = "Adjustment"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,Just True)

-- | Get the value of the “@adjustment@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' scrollbar #adjustment
-- @
getScrollbarAdjustment :: (MonadIO m, IsScrollbar o) => o -> m Gtk.Adjustment.Adjustment
getScrollbarAdjustment :: o -> m Adjustment
getScrollbarAdjustment obj :: o
obj = IO Adjustment -> m Adjustment
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
$ Text -> IO (Maybe Adjustment) -> IO Adjustment
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getScrollbarAdjustment" (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 "adjustment" ManagedPtr Adjustment -> Adjustment
Gtk.Adjustment.Adjustment

-- | Set the value of the “@adjustment@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' scrollbar [ #adjustment 'Data.GI.Base.Attributes.:=' value ]
-- @
setScrollbarAdjustment :: (MonadIO m, IsScrollbar o, Gtk.Adjustment.IsAdjustment a) => o -> a -> m ()
setScrollbarAdjustment :: o -> a -> m ()
setScrollbarAdjustment obj :: o
obj val :: a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "adjustment" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@adjustment@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructScrollbarAdjustment :: (IsScrollbar o, Gtk.Adjustment.IsAdjustment a) => a -> IO (GValueConstruct o)
constructScrollbarAdjustment :: a -> IO (GValueConstruct o)
constructScrollbarAdjustment val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "adjustment" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@adjustment@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #adjustment
-- @
clearScrollbarAdjustment :: (MonadIO m, IsScrollbar o) => o -> m ()
clearScrollbarAdjustment :: o -> m ()
clearScrollbarAdjustment obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Adjustment -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "adjustment" (Maybe Adjustment
forall a. Maybe a
Nothing :: Maybe Gtk.Adjustment.Adjustment)

#if defined(ENABLE_OVERLOADING)
data ScrollbarAdjustmentPropertyInfo
instance AttrInfo ScrollbarAdjustmentPropertyInfo where
    type AttrAllowedOps ScrollbarAdjustmentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ScrollbarAdjustmentPropertyInfo = IsScrollbar
    type AttrSetTypeConstraint ScrollbarAdjustmentPropertyInfo = Gtk.Adjustment.IsAdjustment
    type AttrTransferTypeConstraint ScrollbarAdjustmentPropertyInfo = Gtk.Adjustment.IsAdjustment
    type AttrTransferType ScrollbarAdjustmentPropertyInfo = Gtk.Adjustment.Adjustment
    type AttrGetType ScrollbarAdjustmentPropertyInfo = Gtk.Adjustment.Adjustment
    type AttrLabel ScrollbarAdjustmentPropertyInfo = "adjustment"
    type AttrOrigin ScrollbarAdjustmentPropertyInfo = Scrollbar
    attrGet = getScrollbarAdjustment
    attrSet = setScrollbarAdjustment
    attrTransfer _ v = do
        unsafeCastTo Gtk.Adjustment.Adjustment v
    attrConstruct = constructScrollbarAdjustment
    attrClear = clearScrollbarAdjustment
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Scrollbar
type instance O.AttributeList Scrollbar = ScrollbarAttributeList
type ScrollbarAttributeList = ('[ '("adjustment", ScrollbarAdjustmentPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("surface", Gtk.Widget.WidgetSurfacePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
scrollbarAdjustment :: AttrLabelProxy "adjustment"
scrollbarAdjustment = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Scrollbar = ScrollbarSignalList
type ScrollbarSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("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), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

-- method Scrollbar::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "orientation"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Orientation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scrollbar\8217s orientation."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "adjustment"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Adjustment" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #GtkAdjustment to use, or %NULL to create a new adjustment."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Scrollbar" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_scrollbar_new" gtk_scrollbar_new :: 
    CUInt ->                                -- orientation : TInterface (Name {namespace = "Gtk", name = "Orientation"})
    Ptr Gtk.Adjustment.Adjustment ->        -- adjustment : TInterface (Name {namespace = "Gtk", name = "Adjustment"})
    IO (Ptr Scrollbar)

-- | Creates a new scrollbar with the given orientation.
scrollbarNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Adjustment.IsAdjustment a) =>
    Gtk.Enums.Orientation
    -- ^ /@orientation@/: the scrollbar’s orientation.
    -> Maybe (a)
    -- ^ /@adjustment@/: the t'GI.Gtk.Objects.Adjustment.Adjustment' to use, or 'P.Nothing' to create a new adjustment.
    -> m Scrollbar
    -- ^ __Returns:__ the new t'GI.Gtk.Objects.Scrollbar.Scrollbar'.
scrollbarNew :: Orientation -> Maybe a -> m Scrollbar
scrollbarNew orientation :: Orientation
orientation adjustment :: Maybe a
adjustment = IO Scrollbar -> m Scrollbar
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Scrollbar -> m Scrollbar) -> IO Scrollbar -> m Scrollbar
forall a b. (a -> b) -> a -> b
$ do
    let orientation' :: CUInt
orientation' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Orientation -> Int) -> Orientation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Orientation -> Int
forall a. Enum a => a -> Int
fromEnum) Orientation
orientation
    Ptr Adjustment
maybeAdjustment <- case Maybe a
adjustment of
        Nothing -> Ptr Adjustment -> IO (Ptr Adjustment)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Adjustment
forall a. Ptr a
nullPtr
        Just jAdjustment :: a
jAdjustment -> do
            Ptr Adjustment
jAdjustment' <- a -> IO (Ptr Adjustment)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jAdjustment
            Ptr Adjustment -> IO (Ptr Adjustment)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Adjustment
jAdjustment'
    Ptr Scrollbar
result <- CUInt -> Ptr Adjustment -> IO (Ptr Scrollbar)
gtk_scrollbar_new CUInt
orientation' Ptr Adjustment
maybeAdjustment
    Text -> Ptr Scrollbar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "scrollbarNew" Ptr Scrollbar
result
    Scrollbar
result' <- ((ManagedPtr Scrollbar -> Scrollbar)
-> Ptr Scrollbar -> IO Scrollbar
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Scrollbar -> Scrollbar
Scrollbar) Ptr Scrollbar
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
adjustment a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Scrollbar -> IO Scrollbar
forall (m :: * -> *) a. Monad m => a -> m a
return Scrollbar
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_scrollbar_get_adjustment" gtk_scrollbar_get_adjustment :: 
    Ptr Scrollbar ->                        -- self : TInterface (Name {namespace = "Gtk", name = "Scrollbar"})
    IO (Ptr Gtk.Adjustment.Adjustment)

-- | Returns the scrollbar\'s adjustment.
scrollbarGetAdjustment ::
    (B.CallStack.HasCallStack, MonadIO m, IsScrollbar a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.Scrollbar.Scrollbar'
    -> m Gtk.Adjustment.Adjustment
    -- ^ __Returns:__ the scrollbar\'s adjustment
scrollbarGetAdjustment :: a -> m Adjustment
scrollbarGetAdjustment self :: a
self = IO Adjustment -> m Adjustment
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 Scrollbar
self' <- a -> IO (Ptr Scrollbar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Adjustment
result <- Ptr Scrollbar -> IO (Ptr Adjustment)
gtk_scrollbar_get_adjustment Ptr Scrollbar
self'
    Text -> Ptr Adjustment -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "scrollbarGetAdjustment" 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
self
    Adjustment -> IO Adjustment
forall (m :: * -> *) a. Monad m => a -> m a
return Adjustment
result'

#if defined(ENABLE_OVERLOADING)
data ScrollbarGetAdjustmentMethodInfo
instance (signature ~ (m Gtk.Adjustment.Adjustment), MonadIO m, IsScrollbar a) => O.MethodInfo ScrollbarGetAdjustmentMethodInfo a signature where
    overloadedMethod = scrollbarGetAdjustment

#endif

-- method Scrollbar::set_adjustment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Scrollbar" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkScrollbar" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "adjustment"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Adjustment" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the adjustment to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_scrollbar_set_adjustment" gtk_scrollbar_set_adjustment :: 
    Ptr Scrollbar ->                        -- self : TInterface (Name {namespace = "Gtk", name = "Scrollbar"})
    Ptr Gtk.Adjustment.Adjustment ->        -- adjustment : TInterface (Name {namespace = "Gtk", name = "Adjustment"})
    IO ()

-- | Makes the scrollbar use the given adjustment.
scrollbarSetAdjustment ::
    (B.CallStack.HasCallStack, MonadIO m, IsScrollbar a, Gtk.Adjustment.IsAdjustment b) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.Scrollbar.Scrollbar'
    -> Maybe (b)
    -- ^ /@adjustment@/: the adjustment to set
    -> m ()
scrollbarSetAdjustment :: a -> Maybe b -> m ()
scrollbarSetAdjustment self :: a
self adjustment :: Maybe b
adjustment = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Scrollbar
self' <- a -> IO (Ptr Scrollbar)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Adjustment
maybeAdjustment <- case Maybe b
adjustment of
        Nothing -> Ptr Adjustment -> IO (Ptr Adjustment)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Adjustment
forall a. Ptr a
nullPtr
        Just jAdjustment :: b
jAdjustment -> do
            Ptr Adjustment
jAdjustment' <- b -> IO (Ptr Adjustment)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jAdjustment
            Ptr Adjustment -> IO (Ptr Adjustment)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Adjustment
jAdjustment'
    Ptr Scrollbar -> Ptr Adjustment -> IO ()
gtk_scrollbar_set_adjustment Ptr Scrollbar
self' Ptr Adjustment
maybeAdjustment
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
adjustment b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ScrollbarSetAdjustmentMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsScrollbar a, Gtk.Adjustment.IsAdjustment b) => O.MethodInfo ScrollbarSetAdjustmentMethodInfo a signature where
    overloadedMethod = scrollbarSetAdjustment

#endif