{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An interface for swipeable widgets.
-- 
-- The @AdwSwipeable@ interface is implemented by all swipeable widgets.
-- 
-- See [class/@swipeTracker@/] for details about implementing it.

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

module GI.Adw.Interfaces.Swipeable
    ( 

-- * Exported types
    Swipeable(..)                           ,
    IsSwipeable                             ,
    toSwipeable                             ,


 -- * 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"), [updateNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:updateNextAccessibleSibling"), [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
-- [getAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleParent"), [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"), [getAtContext]("GI.Gtk.Interfaces.Accessible#g:method:getAtContext"), [getBounds]("GI.Gtk.Interfaces.Accessible#g:method:getBounds"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getCancelProgress]("GI.Adw.Interfaces.Swipeable#g:method:getCancelProgress"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getColor]("GI.Gtk.Objects.Widget#g:method:getColor"), [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"), [getDistance]("GI.Adw.Interfaces.Swipeable#g:method:getDistance"), [getFirstAccessibleChild]("GI.Gtk.Interfaces.Accessible#g:method:getFirstAccessibleChild"), [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"), [getNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:getNextAccessibleSibling"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPlatformState]("GI.Gtk.Interfaces.Accessible#g:method:getPlatformState"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProgress]("GI.Adw.Interfaces.Swipeable#g:method:getProgress"), [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"), [getSnapPoints]("GI.Adw.Interfaces.Swipeable#g:method:getSnapPoints"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getSwipeArea]("GI.Adw.Interfaces.Swipeable#g:method:getSwipeArea"), [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
-- [setAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:setAccessibleParent"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [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"), [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)
    ResolveSwipeableMethod                  ,
#endif

-- ** getCancelProgress #method:getCancelProgress#

#if defined(ENABLE_OVERLOADING)
    SwipeableGetCancelProgressMethodInfo    ,
#endif
    swipeableGetCancelProgress              ,


-- ** getDistance #method:getDistance#

#if defined(ENABLE_OVERLOADING)
    SwipeableGetDistanceMethodInfo          ,
#endif
    swipeableGetDistance                    ,


-- ** getProgress #method:getProgress#

#if defined(ENABLE_OVERLOADING)
    SwipeableGetProgressMethodInfo          ,
#endif
    swipeableGetProgress                    ,


-- ** getSnapPoints #method:getSnapPoints#

#if defined(ENABLE_OVERLOADING)
    SwipeableGetSnapPointsMethodInfo        ,
#endif
    swipeableGetSnapPoints                  ,


-- ** getSwipeArea #method:getSwipeArea#

#if defined(ENABLE_OVERLOADING)
    SwipeableGetSwipeAreaMethodInfo         ,
#endif
    swipeableGetSwipeArea                   ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.Adw.Enums as Adw.Enums
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "adw_swipeable_get_type"
    c_adw_swipeable_get_type :: IO B.Types.GType

instance B.Types.TypedObject Swipeable where
    glibType :: IO GType
glibType = IO GType
c_adw_swipeable_get_type

instance B.Types.GObject Swipeable

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

instance O.HasParentTypes Swipeable
type instance O.ParentTypes Swipeable = '[Gtk.Widget.Widget, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Swipeable
type instance O.AttributeList Swipeable = SwipeableAttributeList
type SwipeableAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("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), '("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, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

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

#endif

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

#endif

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

foreign import ccall "adw_swipeable_get_cancel_progress" adw_swipeable_get_cancel_progress :: 
    Ptr Swipeable ->                        -- self : TInterface (Name {namespace = "Adw", name = "Swipeable"})
    IO CDouble

-- | Gets the progress /@self@/ will snap back to after the gesture is canceled.
swipeableGetCancelProgress ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwipeable a) =>
    a
    -- ^ /@self@/: a swipeable
    -> m Double
    -- ^ __Returns:__ the cancel progress, unitless
swipeableGetCancelProgress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwipeable a) =>
a -> m Double
swipeableGetCancelProgress a
self = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Swipeable
self' <- a -> IO (Ptr Swipeable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CDouble
result <- Ptr Swipeable -> IO CDouble
adw_swipeable_get_cancel_progress Ptr Swipeable
self'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data SwipeableGetCancelProgressMethodInfo
instance (signature ~ (m Double), MonadIO m, IsSwipeable a) => O.OverloadedMethod SwipeableGetCancelProgressMethodInfo a signature where
    overloadedMethod = swipeableGetCancelProgress

instance O.OverloadedMethodInfo SwipeableGetCancelProgressMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Interfaces.Swipeable.swipeableGetCancelProgress",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.5/docs/GI-Adw-Interfaces-Swipeable.html#v:swipeableGetCancelProgress"
        })


#endif

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

foreign import ccall "adw_swipeable_get_distance" adw_swipeable_get_distance :: 
    Ptr Swipeable ->                        -- self : TInterface (Name {namespace = "Adw", name = "Swipeable"})
    IO CDouble

-- | Gets the swipe distance of /@self@/.
-- 
-- This corresponds to how many pixels 1 unit represents.
swipeableGetDistance ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwipeable a) =>
    a
    -- ^ /@self@/: a swipeable
    -> m Double
    -- ^ __Returns:__ the swipe distance in pixels
swipeableGetDistance :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwipeable a) =>
a -> m Double
swipeableGetDistance a
self = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Swipeable
self' <- a -> IO (Ptr Swipeable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CDouble
result <- Ptr Swipeable -> IO CDouble
adw_swipeable_get_distance Ptr Swipeable
self'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data SwipeableGetDistanceMethodInfo
instance (signature ~ (m Double), MonadIO m, IsSwipeable a) => O.OverloadedMethod SwipeableGetDistanceMethodInfo a signature where
    overloadedMethod = swipeableGetDistance

instance O.OverloadedMethodInfo SwipeableGetDistanceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Interfaces.Swipeable.swipeableGetDistance",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.5/docs/GI-Adw-Interfaces-Swipeable.html#v:swipeableGetDistance"
        })


#endif

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

foreign import ccall "adw_swipeable_get_progress" adw_swipeable_get_progress :: 
    Ptr Swipeable ->                        -- self : TInterface (Name {namespace = "Adw", name = "Swipeable"})
    IO CDouble

-- | Gets the current progress of /@self@/.
swipeableGetProgress ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwipeable a) =>
    a
    -- ^ /@self@/: a swipeable
    -> m Double
    -- ^ __Returns:__ the current progress, unitless
swipeableGetProgress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwipeable a) =>
a -> m Double
swipeableGetProgress a
self = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Swipeable
self' <- a -> IO (Ptr Swipeable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CDouble
result <- Ptr Swipeable -> IO CDouble
adw_swipeable_get_progress Ptr Swipeable
self'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data SwipeableGetProgressMethodInfo
instance (signature ~ (m Double), MonadIO m, IsSwipeable a) => O.OverloadedMethod SwipeableGetProgressMethodInfo a signature where
    overloadedMethod = swipeableGetProgress

instance O.OverloadedMethodInfo SwipeableGetProgressMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Interfaces.Swipeable.swipeableGetProgress",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.5/docs/GI-Adw-Interfaces-Swipeable.html#v:swipeableGetProgress"
        })


#endif

-- method Swipeable::get_snap_points
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "Swipeable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a swipeable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_snap_points"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "location to return the number of the snap points"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_snap_points"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "location to return the number of the snap points"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TDouble))
-- throws : False
-- Skip return : False

foreign import ccall "adw_swipeable_get_snap_points" adw_swipeable_get_snap_points :: 
    Ptr Swipeable ->                        -- self : TInterface (Name {namespace = "Adw", name = "Swipeable"})
    Ptr Int32 ->                            -- n_snap_points : TBasicType TInt
    IO (Ptr CDouble)

-- | Gets the snap points of /@self@/.
-- 
-- Each snap point represents a progress value that is considered acceptable to
-- end the swipe on.
swipeableGetSnapPoints ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwipeable a) =>
    a
    -- ^ /@self@/: a swipeable
    -> m [Double]
    -- ^ __Returns:__ the snap points
swipeableGetSnapPoints :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwipeable a) =>
a -> m [Double]
swipeableGetSnapPoints a
self = IO [Double] -> m [Double]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Double] -> m [Double]) -> IO [Double] -> m [Double]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Swipeable
self' <- a -> IO (Ptr Swipeable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Int32
nSnapPoints <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr CDouble
result <- Ptr Swipeable -> Ptr Int32 -> IO (Ptr CDouble)
adw_swipeable_get_snap_points Ptr Swipeable
self' Ptr Int32
nSnapPoints
    Int32
nSnapPoints' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nSnapPoints
    Text -> Ptr CDouble -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"swipeableGetSnapPoints" Ptr CDouble
result
    [Double]
result' <- ((CDouble -> Double) -> Int32 -> Ptr CDouble -> IO [Double]
forall a b c.
(Integral a, Storable b) =>
(b -> c) -> a -> Ptr b -> IO [c]
unpackMapStorableArrayWithLength CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Int32
nSnapPoints') Ptr CDouble
result
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nSnapPoints
    [Double] -> IO [Double]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Double]
result'

#if defined(ENABLE_OVERLOADING)
data SwipeableGetSnapPointsMethodInfo
instance (signature ~ (m [Double]), MonadIO m, IsSwipeable a) => O.OverloadedMethod SwipeableGetSnapPointsMethodInfo a signature where
    overloadedMethod = swipeableGetSnapPoints

instance O.OverloadedMethodInfo SwipeableGetSnapPointsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Interfaces.Swipeable.swipeableGetSnapPoints",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.5/docs/GI-Adw-Interfaces-Swipeable.html#v:swipeableGetSnapPoints"
        })


#endif

-- method Swipeable::get_swipe_area
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "Swipeable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a swipeable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "navigation_direction"
--           , argType =
--               TInterface
--                 Name { namespace = "Adw" , name = "NavigationDirection" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the direction of the swipe"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_drag"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether the swipe is caused by a dragging gesture"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rect"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a pointer to a rectangle to store the swipe area"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_swipeable_get_swipe_area" adw_swipeable_get_swipe_area :: 
    Ptr Swipeable ->                        -- self : TInterface (Name {namespace = "Adw", name = "Swipeable"})
    CUInt ->                                -- navigation_direction : TInterface (Name {namespace = "Adw", name = "NavigationDirection"})
    CInt ->                                 -- is_drag : TBasicType TBoolean
    Ptr Gdk.Rectangle.Rectangle ->          -- rect : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    IO ()

-- | Gets the area /@self@/ can start a swipe from for the given direction and
-- gesture type.
-- 
-- This can be used to restrict swipes to only be possible from a certain area,
-- for example, to only allow edge swipes, or to have a draggable element and
-- ignore swipes elsewhere.
-- 
-- If not implemented, the default implementation returns the allocation of
-- /@self@/, allowing swipes from anywhere.
swipeableGetSwipeArea ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwipeable a) =>
    a
    -- ^ /@self@/: a swipeable
    -> Adw.Enums.NavigationDirection
    -- ^ /@navigationDirection@/: the direction of the swipe
    -> Bool
    -- ^ /@isDrag@/: whether the swipe is caused by a dragging gesture
    -> m (Gdk.Rectangle.Rectangle)
swipeableGetSwipeArea :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwipeable a) =>
a -> NavigationDirection -> Bool -> m Rectangle
swipeableGetSwipeArea a
self NavigationDirection
navigationDirection Bool
isDrag = IO Rectangle -> m Rectangle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr Swipeable
self' <- a -> IO (Ptr Swipeable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let navigationDirection' :: CUInt
navigationDirection' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (NavigationDirection -> Int) -> NavigationDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NavigationDirection -> Int
forall a. Enum a => a -> Int
fromEnum) NavigationDirection
navigationDirection
    let isDrag' :: CInt
isDrag' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
isDrag
    Ptr Rectangle
rect <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Gdk.Rectangle.Rectangle)
    Ptr Swipeable -> CUInt -> CInt -> Ptr Rectangle -> IO ()
adw_swipeable_get_swipe_area Ptr Swipeable
self' CUInt
navigationDirection' CInt
isDrag' Ptr Rectangle
rect
    Rectangle
rect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Gdk.Rectangle.Rectangle) Ptr Rectangle
rect
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Rectangle -> IO Rectangle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
rect'

#if defined(ENABLE_OVERLOADING)
data SwipeableGetSwipeAreaMethodInfo
instance (signature ~ (Adw.Enums.NavigationDirection -> Bool -> m (Gdk.Rectangle.Rectangle)), MonadIO m, IsSwipeable a) => O.OverloadedMethod SwipeableGetSwipeAreaMethodInfo a signature where
    overloadedMethod = swipeableGetSwipeArea

instance O.OverloadedMethodInfo SwipeableGetSwipeAreaMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Interfaces.Swipeable.swipeableGetSwipeArea",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.5/docs/GI-Adw-Interfaces-Swipeable.html#v:swipeableGetSwipeArea"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Swipeable = SwipeableSignalList
type SwipeableSignalList = ('[ '("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, DK.Type)])

#endif