{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A lines indicator for [class/@carousel@/].
-- 
-- \<picture>
--   \<source srcset=\"carousel-indicator-dots-lines.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img src=\"carousel-indicator-lines.png\" alt=\"carousel-indicator-lines\">
-- \<\/picture>
-- 
-- The @AdwCarouselIndicatorLines@ widget shows a set of lines for each page of
-- a given [class/@carousel@/]. The carousel\'s active page is shown as another line
-- that moves between them to match the carousel\'s position.
-- 
-- See also [class/@carouselIndicatorDots@/].
-- 
-- == CSS nodes
-- 
-- @AdwCarouselIndicatorLines@ has a single CSS node with name
-- @carouselindicatorlines@.
-- 
-- /Since: 1.0/

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

module GI.Adw.Objects.CarouselIndicatorLines
    ( 

-- * Exported types
    CarouselIndicatorLines(..)              ,
    IsCarouselIndicatorLines                ,
    toCarouselIndicatorLines                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [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"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [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"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getCarousel]("GI.Adw.Objects.CarouselIndicatorLines#g:method:getCarousel"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [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"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOrientation]("GI.Gtk.Interfaces.Orientable#g:method:getOrientation"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [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"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setCarousel]("GI.Adw.Objects.CarouselIndicatorLines#g:method:setCarousel"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [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"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOrientation]("GI.Gtk.Interfaces.Orientable#g:method:setOrientation"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [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").

#if defined(ENABLE_OVERLOADING)
    ResolveCarouselIndicatorLinesMethod     ,
#endif

-- ** getCarousel #method:getCarousel#

#if defined(ENABLE_OVERLOADING)
    CarouselIndicatorLinesGetCarouselMethodInfo,
#endif
    carouselIndicatorLinesGetCarousel       ,


-- ** new #method:new#

    carouselIndicatorLinesNew               ,


-- ** setCarousel #method:setCarousel#

#if defined(ENABLE_OVERLOADING)
    CarouselIndicatorLinesSetCarouselMethodInfo,
#endif
    carouselIndicatorLinesSetCarousel       ,




 -- * Properties


-- ** carousel #attr:carousel#
-- | The displayed carousel.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    CarouselIndicatorLinesCarouselPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    carouselIndicatorLinesCarousel          ,
#endif
    clearCarouselIndicatorLinesCarousel     ,
    constructCarouselIndicatorLinesCarousel ,
    getCarouselIndicatorLinesCarousel       ,
    setCarouselIndicatorLinesCarousel       ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.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 {-# SOURCE #-} qualified GI.Adw.Objects.Carousel as Adw.Carousel
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "adw_carousel_indicator_lines_get_type"
    c_adw_carousel_indicator_lines_get_type :: IO B.Types.GType

instance B.Types.TypedObject CarouselIndicatorLines where
    glibType :: IO GType
glibType = IO GType
c_adw_carousel_indicator_lines_get_type

instance B.Types.GObject CarouselIndicatorLines

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

instance O.HasParentTypes CarouselIndicatorLines
type instance O.ParentTypes CarouselIndicatorLines = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget, Gtk.Orientable.Orientable]

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

-- | Convert 'CarouselIndicatorLines' 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 CarouselIndicatorLines) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_adw_carousel_indicator_lines_get_type
    gvalueSet_ :: Ptr GValue -> Maybe CarouselIndicatorLines -> IO ()
gvalueSet_ Ptr GValue
gv Maybe CarouselIndicatorLines
P.Nothing = Ptr GValue -> Ptr CarouselIndicatorLines -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr CarouselIndicatorLines
forall a. Ptr a
FP.nullPtr :: FP.Ptr CarouselIndicatorLines)
    gvalueSet_ Ptr GValue
gv (P.Just CarouselIndicatorLines
obj) = CarouselIndicatorLines
-> (Ptr CarouselIndicatorLines -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CarouselIndicatorLines
obj (Ptr GValue -> Ptr CarouselIndicatorLines -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe CarouselIndicatorLines)
gvalueGet_ Ptr GValue
gv = do
        Ptr CarouselIndicatorLines
ptr <- Ptr GValue -> IO (Ptr CarouselIndicatorLines)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr CarouselIndicatorLines)
        if Ptr CarouselIndicatorLines
ptr Ptr CarouselIndicatorLines -> Ptr CarouselIndicatorLines -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CarouselIndicatorLines
forall a. Ptr a
FP.nullPtr
        then CarouselIndicatorLines -> Maybe CarouselIndicatorLines
forall a. a -> Maybe a
P.Just (CarouselIndicatorLines -> Maybe CarouselIndicatorLines)
-> IO CarouselIndicatorLines -> IO (Maybe CarouselIndicatorLines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr CarouselIndicatorLines -> CarouselIndicatorLines)
-> Ptr CarouselIndicatorLines -> IO CarouselIndicatorLines
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr CarouselIndicatorLines -> CarouselIndicatorLines
CarouselIndicatorLines Ptr CarouselIndicatorLines
ptr
        else Maybe CarouselIndicatorLines -> IO (Maybe CarouselIndicatorLines)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CarouselIndicatorLines
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveCarouselIndicatorLinesMethod (t :: Symbol) (o :: *) :: * where
    ResolveCarouselIndicatorLinesMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveCarouselIndicatorLinesMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveCarouselIndicatorLinesMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveCarouselIndicatorLinesMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveCarouselIndicatorLinesMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveCarouselIndicatorLinesMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveCarouselIndicatorLinesMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveCarouselIndicatorLinesMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveCarouselIndicatorLinesMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveCarouselIndicatorLinesMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCarouselIndicatorLinesMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCarouselIndicatorLinesMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveCarouselIndicatorLinesMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveCarouselIndicatorLinesMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveCarouselIndicatorLinesMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveCarouselIndicatorLinesMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveCarouselIndicatorLinesMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveCarouselIndicatorLinesMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveCarouselIndicatorLinesMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveCarouselIndicatorLinesMethod "disposeTemplate" o = Gtk.Widget.WidgetDisposeTemplateMethodInfo
    ResolveCarouselIndicatorLinesMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveCarouselIndicatorLinesMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveCarouselIndicatorLinesMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCarouselIndicatorLinesMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCarouselIndicatorLinesMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCarouselIndicatorLinesMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveCarouselIndicatorLinesMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveCarouselIndicatorLinesMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveCarouselIndicatorLinesMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveCarouselIndicatorLinesMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveCarouselIndicatorLinesMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveCarouselIndicatorLinesMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveCarouselIndicatorLinesMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveCarouselIndicatorLinesMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveCarouselIndicatorLinesMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveCarouselIndicatorLinesMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveCarouselIndicatorLinesMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveCarouselIndicatorLinesMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveCarouselIndicatorLinesMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCarouselIndicatorLinesMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveCarouselIndicatorLinesMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveCarouselIndicatorLinesMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveCarouselIndicatorLinesMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveCarouselIndicatorLinesMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveCarouselIndicatorLinesMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveCarouselIndicatorLinesMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveCarouselIndicatorLinesMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveCarouselIndicatorLinesMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCarouselIndicatorLinesMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCarouselIndicatorLinesMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveCarouselIndicatorLinesMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveCarouselIndicatorLinesMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveCarouselIndicatorLinesMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveCarouselIndicatorLinesMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveCarouselIndicatorLinesMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveCarouselIndicatorLinesMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveCarouselIndicatorLinesMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCarouselIndicatorLinesMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCarouselIndicatorLinesMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveCarouselIndicatorLinesMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveCarouselIndicatorLinesMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveCarouselIndicatorLinesMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveCarouselIndicatorLinesMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveCarouselIndicatorLinesMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveCarouselIndicatorLinesMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveCarouselIndicatorLinesMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCarouselIndicatorLinesMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveCarouselIndicatorLinesMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveCarouselIndicatorLinesMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveCarouselIndicatorLinesMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveCarouselIndicatorLinesMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCarouselIndicatorLinesMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCarouselIndicatorLinesMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCarouselIndicatorLinesMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveCarouselIndicatorLinesMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveCarouselIndicatorLinesMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveCarouselIndicatorLinesMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveCarouselIndicatorLinesMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveCarouselIndicatorLinesMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCarouselIndicatorLinesMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveCarouselIndicatorLinesMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveCarouselIndicatorLinesMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveCarouselIndicatorLinesMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveCarouselIndicatorLinesMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCarouselIndicatorLinesMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveCarouselIndicatorLinesMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveCarouselIndicatorLinesMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveCarouselIndicatorLinesMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveCarouselIndicatorLinesMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveCarouselIndicatorLinesMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveCarouselIndicatorLinesMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveCarouselIndicatorLinesMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveCarouselIndicatorLinesMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveCarouselIndicatorLinesMethod "getCarousel" o = CarouselIndicatorLinesGetCarouselMethodInfo
    ResolveCarouselIndicatorLinesMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveCarouselIndicatorLinesMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveCarouselIndicatorLinesMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveCarouselIndicatorLinesMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveCarouselIndicatorLinesMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveCarouselIndicatorLinesMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCarouselIndicatorLinesMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveCarouselIndicatorLinesMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveCarouselIndicatorLinesMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveCarouselIndicatorLinesMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveCarouselIndicatorLinesMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveCarouselIndicatorLinesMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveCarouselIndicatorLinesMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveCarouselIndicatorLinesMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveCarouselIndicatorLinesMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveCarouselIndicatorLinesMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveCarouselIndicatorLinesMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveCarouselIndicatorLinesMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveCarouselIndicatorLinesMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveCarouselIndicatorLinesMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveCarouselIndicatorLinesMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveCarouselIndicatorLinesMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveCarouselIndicatorLinesMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveCarouselIndicatorLinesMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveCarouselIndicatorLinesMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveCarouselIndicatorLinesMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveCarouselIndicatorLinesMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveCarouselIndicatorLinesMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveCarouselIndicatorLinesMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveCarouselIndicatorLinesMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveCarouselIndicatorLinesMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveCarouselIndicatorLinesMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveCarouselIndicatorLinesMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveCarouselIndicatorLinesMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveCarouselIndicatorLinesMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveCarouselIndicatorLinesMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveCarouselIndicatorLinesMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveCarouselIndicatorLinesMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveCarouselIndicatorLinesMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCarouselIndicatorLinesMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCarouselIndicatorLinesMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveCarouselIndicatorLinesMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveCarouselIndicatorLinesMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveCarouselIndicatorLinesMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveCarouselIndicatorLinesMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveCarouselIndicatorLinesMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveCarouselIndicatorLinesMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveCarouselIndicatorLinesMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveCarouselIndicatorLinesMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveCarouselIndicatorLinesMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveCarouselIndicatorLinesMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveCarouselIndicatorLinesMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveCarouselIndicatorLinesMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveCarouselIndicatorLinesMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveCarouselIndicatorLinesMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveCarouselIndicatorLinesMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveCarouselIndicatorLinesMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveCarouselIndicatorLinesMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveCarouselIndicatorLinesMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveCarouselIndicatorLinesMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveCarouselIndicatorLinesMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveCarouselIndicatorLinesMethod "setCarousel" o = CarouselIndicatorLinesSetCarouselMethodInfo
    ResolveCarouselIndicatorLinesMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveCarouselIndicatorLinesMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveCarouselIndicatorLinesMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveCarouselIndicatorLinesMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveCarouselIndicatorLinesMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCarouselIndicatorLinesMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCarouselIndicatorLinesMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveCarouselIndicatorLinesMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveCarouselIndicatorLinesMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveCarouselIndicatorLinesMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveCarouselIndicatorLinesMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveCarouselIndicatorLinesMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveCarouselIndicatorLinesMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveCarouselIndicatorLinesMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveCarouselIndicatorLinesMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveCarouselIndicatorLinesMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveCarouselIndicatorLinesMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveCarouselIndicatorLinesMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveCarouselIndicatorLinesMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveCarouselIndicatorLinesMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveCarouselIndicatorLinesMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveCarouselIndicatorLinesMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveCarouselIndicatorLinesMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveCarouselIndicatorLinesMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveCarouselIndicatorLinesMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveCarouselIndicatorLinesMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveCarouselIndicatorLinesMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCarouselIndicatorLinesMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveCarouselIndicatorLinesMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveCarouselIndicatorLinesMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveCarouselIndicatorLinesMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveCarouselIndicatorLinesMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveCarouselIndicatorLinesMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveCarouselIndicatorLinesMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveCarouselIndicatorLinesMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveCarouselIndicatorLinesMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveCarouselIndicatorLinesMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveCarouselIndicatorLinesMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "carousel"
   -- Type: TInterface (Name {namespace = "Adw", 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' carouselIndicatorLines #carousel
-- @
getCarouselIndicatorLinesCarousel :: (MonadIO m, IsCarouselIndicatorLines o) => o -> m (Maybe Adw.Carousel.Carousel)
getCarouselIndicatorLinesCarousel :: forall (m :: * -> *) o.
(MonadIO m, IsCarouselIndicatorLines o) =>
o -> m (Maybe Carousel)
getCarouselIndicatorLinesCarousel o
obj = IO (Maybe Carousel) -> m (Maybe Carousel)
forall a. IO a -> m a
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
Adw.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' carouselIndicatorLines [ #carousel 'Data.GI.Base.Attributes.:=' value ]
-- @
setCarouselIndicatorLinesCarousel :: (MonadIO m, IsCarouselIndicatorLines o, Adw.Carousel.IsCarousel a) => o -> a -> m ()
setCarouselIndicatorLinesCarousel :: forall (m :: * -> *) o a.
(MonadIO m, IsCarouselIndicatorLines o, IsCarousel a) =>
o -> a -> m ()
setCarouselIndicatorLinesCarousel o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"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`.
constructCarouselIndicatorLinesCarousel :: (IsCarouselIndicatorLines o, MIO.MonadIO m, Adw.Carousel.IsCarousel a) => a -> m (GValueConstruct o)
constructCarouselIndicatorLinesCarousel :: forall o (m :: * -> *) a.
(IsCarouselIndicatorLines o, MonadIO m, IsCarousel a) =>
a -> m (GValueConstruct o)
constructCarouselIndicatorLinesCarousel a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"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
-- @
clearCarouselIndicatorLinesCarousel :: (MonadIO m, IsCarouselIndicatorLines o) => o -> m ()
clearCarouselIndicatorLinesCarousel :: forall (m :: * -> *) o.
(MonadIO m, IsCarouselIndicatorLines o) =>
o -> m ()
clearCarouselIndicatorLinesCarousel o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 Adw.Carousel.Carousel)

#if defined(ENABLE_OVERLOADING)
data CarouselIndicatorLinesCarouselPropertyInfo
instance AttrInfo CarouselIndicatorLinesCarouselPropertyInfo where
    type AttrAllowedOps CarouselIndicatorLinesCarouselPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CarouselIndicatorLinesCarouselPropertyInfo = IsCarouselIndicatorLines
    type AttrSetTypeConstraint CarouselIndicatorLinesCarouselPropertyInfo = Adw.Carousel.IsCarousel
    type AttrTransferTypeConstraint CarouselIndicatorLinesCarouselPropertyInfo = Adw.Carousel.IsCarousel
    type AttrTransferType CarouselIndicatorLinesCarouselPropertyInfo = Adw.Carousel.Carousel
    type AttrGetType CarouselIndicatorLinesCarouselPropertyInfo = (Maybe Adw.Carousel.Carousel)
    type AttrLabel CarouselIndicatorLinesCarouselPropertyInfo = "carousel"
    type AttrOrigin CarouselIndicatorLinesCarouselPropertyInfo = CarouselIndicatorLines
    attrGet = getCarouselIndicatorLinesCarousel
    attrSet = setCarouselIndicatorLinesCarousel
    attrTransfer _ v = do
        unsafeCastTo Adw.Carousel.Carousel v
    attrConstruct = constructCarouselIndicatorLinesCarousel
    attrClear = clearCarouselIndicatorLinesCarousel
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.CarouselIndicatorLines.carousel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-CarouselIndicatorLines.html#g:attr:carousel"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CarouselIndicatorLines
type instance O.AttributeList CarouselIndicatorLines = CarouselIndicatorLinesAttributeList
type CarouselIndicatorLinesAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("carousel", CarouselIndicatorLinesCarouselPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("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), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("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), '("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)
carouselIndicatorLinesCarousel :: AttrLabelProxy "carousel"
carouselIndicatorLinesCarousel = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CarouselIndicatorLines = CarouselIndicatorLinesSignalList
type CarouselIndicatorLinesSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "adw_carousel_indicator_lines_new" adw_carousel_indicator_lines_new :: 
    IO (Ptr CarouselIndicatorLines)

-- | Creates a new @AdwCarouselIndicatorLines@.
-- 
-- /Since: 1.0/
carouselIndicatorLinesNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m CarouselIndicatorLines
    -- ^ __Returns:__ the newly created @AdwCarouselIndicatorLines@
carouselIndicatorLinesNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m CarouselIndicatorLines
carouselIndicatorLinesNew  = IO CarouselIndicatorLines -> m CarouselIndicatorLines
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CarouselIndicatorLines -> m CarouselIndicatorLines)
-> IO CarouselIndicatorLines -> m CarouselIndicatorLines
forall a b. (a -> b) -> a -> b
$ do
    Ptr CarouselIndicatorLines
result <- IO (Ptr CarouselIndicatorLines)
adw_carousel_indicator_lines_new
    Text -> Ptr CarouselIndicatorLines -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"carouselIndicatorLinesNew" Ptr CarouselIndicatorLines
result
    CarouselIndicatorLines
result' <- ((ManagedPtr CarouselIndicatorLines -> CarouselIndicatorLines)
-> Ptr CarouselIndicatorLines -> IO CarouselIndicatorLines
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CarouselIndicatorLines -> CarouselIndicatorLines
CarouselIndicatorLines) Ptr CarouselIndicatorLines
result
    CarouselIndicatorLines -> IO CarouselIndicatorLines
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CarouselIndicatorLines
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "adw_carousel_indicator_lines_get_carousel" adw_carousel_indicator_lines_get_carousel :: 
    Ptr CarouselIndicatorLines ->           -- self : TInterface (Name {namespace = "Adw", name = "CarouselIndicatorLines"})
    IO (Ptr Adw.Carousel.Carousel)

-- | Gets the displayed carousel.
-- 
-- /Since: 1.0/
carouselIndicatorLinesGetCarousel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCarouselIndicatorLines a) =>
    a
    -- ^ /@self@/: an indicator
    -> m (Maybe Adw.Carousel.Carousel)
    -- ^ __Returns:__ the displayed carousel
carouselIndicatorLinesGetCarousel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCarouselIndicatorLines a) =>
a -> m (Maybe Carousel)
carouselIndicatorLinesGetCarousel a
self = IO (Maybe Carousel) -> m (Maybe Carousel)
forall a. IO a -> m a
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 CarouselIndicatorLines
self' <- a -> IO (Ptr CarouselIndicatorLines)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Carousel
result <- Ptr CarouselIndicatorLines -> IO (Ptr Carousel)
adw_carousel_indicator_lines_get_carousel Ptr CarouselIndicatorLines
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
Adw.Carousel.Carousel) Ptr Carousel
result'
        Carousel -> IO Carousel
forall a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Carousel
maybeResult

#if defined(ENABLE_OVERLOADING)
data CarouselIndicatorLinesGetCarouselMethodInfo
instance (signature ~ (m (Maybe Adw.Carousel.Carousel)), MonadIO m, IsCarouselIndicatorLines a) => O.OverloadedMethod CarouselIndicatorLinesGetCarouselMethodInfo a signature where
    overloadedMethod = carouselIndicatorLinesGetCarousel

instance O.OverloadedMethodInfo CarouselIndicatorLinesGetCarouselMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.CarouselIndicatorLines.carouselIndicatorLinesGetCarousel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-CarouselIndicatorLines.html#v:carouselIndicatorLinesGetCarousel"
        })


#endif

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

foreign import ccall "adw_carousel_indicator_lines_set_carousel" adw_carousel_indicator_lines_set_carousel :: 
    Ptr CarouselIndicatorLines ->           -- self : TInterface (Name {namespace = "Adw", name = "CarouselIndicatorLines"})
    Ptr Adw.Carousel.Carousel ->            -- carousel : TInterface (Name {namespace = "Adw", name = "Carousel"})
    IO ()

-- | Sets the displayed carousel.
-- 
-- /Since: 1.0/
carouselIndicatorLinesSetCarousel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCarouselIndicatorLines a, Adw.Carousel.IsCarousel b) =>
    a
    -- ^ /@self@/: an indicator
    -> Maybe (b)
    -- ^ /@carousel@/: a carousel
    -> m ()
carouselIndicatorLinesSetCarousel :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCarouselIndicatorLines a,
 IsCarousel b) =>
a -> Maybe b -> m ()
carouselIndicatorLinesSetCarousel a
self Maybe b
carousel = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CarouselIndicatorLines
self' <- a -> IO (Ptr CarouselIndicatorLines)
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Carousel
jCarousel'
    Ptr CarouselIndicatorLines -> Ptr Carousel -> IO ()
adw_carousel_indicator_lines_set_carousel Ptr CarouselIndicatorLines
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CarouselIndicatorLinesSetCarouselMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsCarouselIndicatorLines a, Adw.Carousel.IsCarousel b) => O.OverloadedMethod CarouselIndicatorLinesSetCarouselMethodInfo a signature where
    overloadedMethod = carouselIndicatorLinesSetCarousel

instance O.OverloadedMethodInfo CarouselIndicatorLinesSetCarouselMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.CarouselIndicatorLines.carouselIndicatorLinesSetCarousel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-CarouselIndicatorLines.html#v:carouselIndicatorLinesSetCarousel"
        })


#endif