{-# LANGUAGE TypeApplications #-}


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

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

module GI.Handy.Objects.CarouselIndicatorDots
    ( 

-- * Exported types
    CarouselIndicatorDots(..)               ,
    IsCarouselIndicatorDots                 ,
    toCarouselIndicatorDots                 ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveCarouselIndicatorDotsMethod      ,
#endif

-- ** getCarousel #method:getCarousel#

#if defined(ENABLE_OVERLOADING)
    CarouselIndicatorDotsGetCarouselMethodInfo,
#endif
    carouselIndicatorDotsGetCarousel        ,


-- ** new #method:new#

    carouselIndicatorDotsNew                ,


-- ** setCarousel #method:setCarousel#

#if defined(ENABLE_OVERLOADING)
    CarouselIndicatorDotsSetCarouselMethodInfo,
#endif
    carouselIndicatorDotsSetCarousel        ,




 -- * Properties


-- ** carousel #attr:carousel#
-- | The t'GI.Handy.Objects.Carousel.Carousel' the indicator uses.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    CarouselIndicatorDotsCarouselPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    carouselIndicatorDotsCarousel           ,
#endif
    clearCarouselIndicatorDotsCarousel      ,
    constructCarouselIndicatorDotsCarousel  ,
    getCarouselIndicatorDotsCarousel        ,
    setCarouselIndicatorDotsCarousel        ,




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

import qualified GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import qualified GI.Gtk.Objects.DrawingArea as Gtk.DrawingArea
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Handy.Objects.Carousel as Handy.Carousel

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

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

foreign import ccall "hdy_carousel_indicator_dots_get_type"
    c_hdy_carousel_indicator_dots_get_type :: IO B.Types.GType

instance B.Types.TypedObject CarouselIndicatorDots where
    glibType :: IO GType
glibType = IO GType
c_hdy_carousel_indicator_dots_get_type

instance B.Types.GObject CarouselIndicatorDots

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

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

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

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

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

instance (info ~ ResolveCarouselIndicatorDotsMethod t CarouselIndicatorDots, O.OverloadedMethod info CarouselIndicatorDots p) => OL.IsLabel t (CarouselIndicatorDots -> 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 ~ ResolveCarouselIndicatorDotsMethod t CarouselIndicatorDots, O.OverloadedMethod info CarouselIndicatorDots p, R.HasField t CarouselIndicatorDots p) => R.HasField t CarouselIndicatorDots p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "carousel"
   -- Type: TInterface (Name {namespace = "Handy", name = "Carousel"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@carousel@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' carouselIndicatorDots #carousel
-- @
getCarouselIndicatorDotsCarousel :: (MonadIO m, IsCarouselIndicatorDots o) => o -> m (Maybe Handy.Carousel.Carousel)
getCarouselIndicatorDotsCarousel :: forall (m :: * -> *) o.
(MonadIO m, IsCarouselIndicatorDots o) =>
o -> m (Maybe Carousel)
getCarouselIndicatorDotsCarousel o
obj = IO (Maybe Carousel) -> m (Maybe Carousel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Carousel) -> m (Maybe Carousel))
-> IO (Maybe Carousel) -> m (Maybe Carousel)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr Carousel -> Carousel)
-> IO (Maybe Carousel)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"carousel" ManagedPtr Carousel -> Carousel
Handy.Carousel.Carousel

-- | Set the value of the “@carousel@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' carouselIndicatorDots [ #carousel 'Data.GI.Base.Attributes.:=' value ]
-- @
setCarouselIndicatorDotsCarousel :: (MonadIO m, IsCarouselIndicatorDots o, Handy.Carousel.IsCarousel a) => o -> a -> m ()
setCarouselIndicatorDotsCarousel :: forall (m :: * -> *) o a.
(MonadIO m, IsCarouselIndicatorDots o, IsCarousel a) =>
o -> a -> m ()
setCarouselIndicatorDotsCarousel o
obj a
val = IO () -> m ()
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
"carousel" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@carousel@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCarouselIndicatorDotsCarousel :: (IsCarouselIndicatorDots o, MIO.MonadIO m, Handy.Carousel.IsCarousel a) => a -> m (GValueConstruct o)
constructCarouselIndicatorDotsCarousel :: forall o (m :: * -> *) a.
(IsCarouselIndicatorDots o, MonadIO m, IsCarousel a) =>
a -> m (GValueConstruct o)
constructCarouselIndicatorDotsCarousel a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
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
"carousel" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@carousel@” 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' #carousel
-- @
clearCarouselIndicatorDotsCarousel :: (MonadIO m, IsCarouselIndicatorDots o) => o -> m ()
clearCarouselIndicatorDotsCarousel :: forall (m :: * -> *) o.
(MonadIO m, IsCarouselIndicatorDots o) =>
o -> m ()
clearCarouselIndicatorDotsCarousel 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 Carousel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"carousel" (Maybe Carousel
forall a. Maybe a
Nothing :: Maybe Handy.Carousel.Carousel)

#if defined(ENABLE_OVERLOADING)
data CarouselIndicatorDotsCarouselPropertyInfo
instance AttrInfo CarouselIndicatorDotsCarouselPropertyInfo where
    type AttrAllowedOps CarouselIndicatorDotsCarouselPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CarouselIndicatorDotsCarouselPropertyInfo = IsCarouselIndicatorDots
    type AttrSetTypeConstraint CarouselIndicatorDotsCarouselPropertyInfo = Handy.Carousel.IsCarousel
    type AttrTransferTypeConstraint CarouselIndicatorDotsCarouselPropertyInfo = Handy.Carousel.IsCarousel
    type AttrTransferType CarouselIndicatorDotsCarouselPropertyInfo = Handy.Carousel.Carousel
    type AttrGetType CarouselIndicatorDotsCarouselPropertyInfo = (Maybe Handy.Carousel.Carousel)
    type AttrLabel CarouselIndicatorDotsCarouselPropertyInfo = "carousel"
    type AttrOrigin CarouselIndicatorDotsCarouselPropertyInfo = CarouselIndicatorDots
    attrGet = getCarouselIndicatorDotsCarousel
    attrSet = setCarouselIndicatorDotsCarousel
    attrTransfer _ v = do
        unsafeCastTo Handy.Carousel.Carousel v
    attrConstruct = constructCarouselIndicatorDotsCarousel
    attrClear = clearCarouselIndicatorDotsCarousel
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.CarouselIndicatorDots.carousel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.1/docs/GI-Handy-Objects-CarouselIndicatorDots.html#g:attr:carousel"
        })
#endif

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

#if defined(ENABLE_OVERLOADING)
carouselIndicatorDotsCarousel :: AttrLabelProxy "carousel"
carouselIndicatorDotsCarousel = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "hdy_carousel_indicator_dots_new" hdy_carousel_indicator_dots_new :: 
    IO (Ptr CarouselIndicatorDots)

-- | Create a new t'GI.Handy.Objects.CarouselIndicatorDots.CarouselIndicatorDots' widget.
-- 
-- /Since: 1.0/
carouselIndicatorDotsNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m CarouselIndicatorDots
    -- ^ __Returns:__ The newly created t'GI.Handy.Objects.CarouselIndicatorDots.CarouselIndicatorDots' widget
carouselIndicatorDotsNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m CarouselIndicatorDots
carouselIndicatorDotsNew  = IO CarouselIndicatorDots -> m CarouselIndicatorDots
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CarouselIndicatorDots -> m CarouselIndicatorDots)
-> IO CarouselIndicatorDots -> m CarouselIndicatorDots
forall a b. (a -> b) -> a -> b
$ do
    Ptr CarouselIndicatorDots
result <- IO (Ptr CarouselIndicatorDots)
hdy_carousel_indicator_dots_new
    Text -> Ptr CarouselIndicatorDots -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"carouselIndicatorDotsNew" Ptr CarouselIndicatorDots
result
    CarouselIndicatorDots
result' <- ((ManagedPtr CarouselIndicatorDots -> CarouselIndicatorDots)
-> Ptr CarouselIndicatorDots -> IO CarouselIndicatorDots
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr CarouselIndicatorDots -> CarouselIndicatorDots
CarouselIndicatorDots) Ptr CarouselIndicatorDots
result
    CarouselIndicatorDots -> IO CarouselIndicatorDots
forall (m :: * -> *) a. Monad m => a -> m a
return CarouselIndicatorDots
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "hdy_carousel_indicator_dots_get_carousel" hdy_carousel_indicator_dots_get_carousel :: 
    Ptr CarouselIndicatorDots ->            -- self : TInterface (Name {namespace = "Handy", name = "CarouselIndicatorDots"})
    IO (Ptr Handy.Carousel.Carousel)

-- | Get the t'GI.Handy.Objects.Carousel.Carousel' the indicator uses.
-- 
-- See: 'GI.Handy.Objects.CarouselIndicatorDots.carouselIndicatorDotsSetCarousel'
-- 
-- /Since: 1.0/
carouselIndicatorDotsGetCarousel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCarouselIndicatorDots a) =>
    a
    -- ^ /@self@/: a t'GI.Handy.Objects.CarouselIndicatorDots.CarouselIndicatorDots'
    -> m (Maybe Handy.Carousel.Carousel)
    -- ^ __Returns:__ the t'GI.Handy.Objects.Carousel.Carousel', or 'P.Nothing' if none has been set
carouselIndicatorDotsGetCarousel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCarouselIndicatorDots a) =>
a -> m (Maybe Carousel)
carouselIndicatorDotsGetCarousel a
self = IO (Maybe Carousel) -> m (Maybe Carousel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Carousel) -> m (Maybe Carousel))
-> IO (Maybe Carousel) -> m (Maybe Carousel)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CarouselIndicatorDots
self' <- a -> IO (Ptr CarouselIndicatorDots)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Carousel
result <- Ptr CarouselIndicatorDots -> IO (Ptr Carousel)
hdy_carousel_indicator_dots_get_carousel Ptr CarouselIndicatorDots
self'
    Maybe Carousel
maybeResult <- Ptr Carousel
-> (Ptr Carousel -> IO Carousel) -> IO (Maybe Carousel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Carousel
result ((Ptr Carousel -> IO Carousel) -> IO (Maybe Carousel))
-> (Ptr Carousel -> IO Carousel) -> IO (Maybe Carousel)
forall a b. (a -> b) -> a -> b
$ \Ptr Carousel
result' -> do
        Carousel
result'' <- ((ManagedPtr Carousel -> Carousel) -> Ptr Carousel -> IO Carousel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Carousel -> Carousel
Handy.Carousel.Carousel) Ptr Carousel
result'
        Carousel -> IO Carousel
forall (m :: * -> *) a. Monad m => a -> m a
return Carousel
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Carousel -> IO (Maybe Carousel)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Carousel
maybeResult

#if defined(ENABLE_OVERLOADING)
data CarouselIndicatorDotsGetCarouselMethodInfo
instance (signature ~ (m (Maybe Handy.Carousel.Carousel)), MonadIO m, IsCarouselIndicatorDots a) => O.OverloadedMethod CarouselIndicatorDotsGetCarouselMethodInfo a signature where
    overloadedMethod = carouselIndicatorDotsGetCarousel

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


#endif

-- method CarouselIndicatorDots::set_carousel
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Handy" , name = "CarouselIndicatorDots" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #HdyCarouselIndicatorDots"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "carousel"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "Carousel" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #HdyCarousel" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_carousel_indicator_dots_set_carousel" hdy_carousel_indicator_dots_set_carousel :: 
    Ptr CarouselIndicatorDots ->            -- self : TInterface (Name {namespace = "Handy", name = "CarouselIndicatorDots"})
    Ptr Handy.Carousel.Carousel ->          -- carousel : TInterface (Name {namespace = "Handy", name = "Carousel"})
    IO ()

-- | Sets the t'GI.Handy.Objects.Carousel.Carousel' to use.
-- 
-- /Since: 1.0/
carouselIndicatorDotsSetCarousel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCarouselIndicatorDots a, Handy.Carousel.IsCarousel b) =>
    a
    -- ^ /@self@/: a t'GI.Handy.Objects.CarouselIndicatorDots.CarouselIndicatorDots'
    -> Maybe (b)
    -- ^ /@carousel@/: a t'GI.Handy.Objects.Carousel.Carousel'
    -> m ()
carouselIndicatorDotsSetCarousel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCarouselIndicatorDots a,
 IsCarousel b) =>
a -> Maybe b -> m ()
carouselIndicatorDotsSetCarousel a
self Maybe b
carousel = 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 CarouselIndicatorDots
self' <- a -> IO (Ptr CarouselIndicatorDots)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Carousel
maybeCarousel <- case Maybe b
carousel of
        Maybe b
Nothing -> Ptr Carousel -> IO (Ptr Carousel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Carousel
forall a. Ptr a
nullPtr
        Just b
jCarousel -> do
            Ptr Carousel
jCarousel' <- b -> IO (Ptr Carousel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCarousel
            Ptr Carousel -> IO (Ptr Carousel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Carousel
jCarousel'
    Ptr CarouselIndicatorDots -> Ptr Carousel -> IO ()
hdy_carousel_indicator_dots_set_carousel Ptr CarouselIndicatorDots
self' Ptr Carousel
maybeCarousel
    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
carousel b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CarouselIndicatorDotsSetCarouselMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsCarouselIndicatorDots a, Handy.Carousel.IsCarousel b) => O.OverloadedMethod CarouselIndicatorDotsSetCarouselMethodInfo a signature where
    overloadedMethod = carouselIndicatorDotsSetCarousel

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


#endif