{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Clutter.Objects.SwipeAction
    ( 
    SwipeAction(..)                         ,
    IsSwipeAction                           ,
    toSwipeAction                           ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveSwipeActionMethod                ,
#endif
    swipeActionNew                          ,
 
    SwipeActionSweptCallback                ,
#if defined(ENABLE_OVERLOADING)
    SwipeActionSweptSignalInfo              ,
#endif
    afterSwipeActionSwept                   ,
    onSwipeActionSwept                      ,
    SwipeActionSwipeCallback                ,
#if defined(ENABLE_OVERLOADING)
    SwipeActionSwipeSignalInfo              ,
#endif
    afterSwipeActionSwipe                   ,
    onSwipeActionSwipe                      ,
    ) 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.Clutter.Flags as Clutter.Flags
import {-# SOURCE #-} qualified GI.Clutter.Objects.Action as Clutter.Action
import {-# SOURCE #-} qualified GI.Clutter.Objects.Actor as Clutter.Actor
import {-# SOURCE #-} qualified GI.Clutter.Objects.ActorMeta as Clutter.ActorMeta
import {-# SOURCE #-} qualified GI.Clutter.Objects.GestureAction as Clutter.GestureAction
import qualified GI.GObject.Objects.Object as GObject.Object
newtype SwipeAction = SwipeAction (SP.ManagedPtr SwipeAction)
    deriving (SwipeAction -> SwipeAction -> Bool
(SwipeAction -> SwipeAction -> Bool)
-> (SwipeAction -> SwipeAction -> Bool) -> Eq SwipeAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SwipeAction -> SwipeAction -> Bool
== :: SwipeAction -> SwipeAction -> Bool
$c/= :: SwipeAction -> SwipeAction -> Bool
/= :: SwipeAction -> SwipeAction -> Bool
Eq)
instance SP.ManagedPtrNewtype SwipeAction where
    toManagedPtr :: SwipeAction -> ManagedPtr SwipeAction
toManagedPtr (SwipeAction ManagedPtr SwipeAction
p) = ManagedPtr SwipeAction
p
foreign import ccall "clutter_swipe_action_get_type"
    c_clutter_swipe_action_get_type :: IO B.Types.GType
instance B.Types.TypedObject SwipeAction where
    glibType :: IO GType
glibType = IO GType
c_clutter_swipe_action_get_type
instance B.Types.GObject SwipeAction
class (SP.GObject o, O.IsDescendantOf SwipeAction o) => IsSwipeAction o
instance (SP.GObject o, O.IsDescendantOf SwipeAction o) => IsSwipeAction o
instance O.HasParentTypes SwipeAction
type instance O.ParentTypes SwipeAction = '[Clutter.GestureAction.GestureAction, Clutter.Action.Action, Clutter.ActorMeta.ActorMeta, GObject.Object.Object]
toSwipeAction :: (MIO.MonadIO m, IsSwipeAction o) => o -> m SwipeAction
toSwipeAction :: forall (m :: * -> *) o.
(MonadIO m, IsSwipeAction o) =>
o -> m SwipeAction
toSwipeAction = IO SwipeAction -> m SwipeAction
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SwipeAction -> m SwipeAction)
-> (o -> IO SwipeAction) -> o -> m SwipeAction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SwipeAction -> SwipeAction) -> o -> IO SwipeAction
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr SwipeAction -> SwipeAction
SwipeAction
instance B.GValue.IsGValue (Maybe SwipeAction) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_clutter_swipe_action_get_type
    gvalueSet_ :: Ptr GValue -> Maybe SwipeAction -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SwipeAction
P.Nothing = Ptr GValue -> Ptr SwipeAction -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SwipeAction
forall a. Ptr a
FP.nullPtr :: FP.Ptr SwipeAction)
    gvalueSet_ Ptr GValue
gv (P.Just SwipeAction
obj) = SwipeAction -> (Ptr SwipeAction -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SwipeAction
obj (Ptr GValue -> Ptr SwipeAction -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe SwipeAction)
gvalueGet_ Ptr GValue
gv = do
        Ptr SwipeAction
ptr <- Ptr GValue -> IO (Ptr SwipeAction)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SwipeAction)
        if Ptr SwipeAction
ptr Ptr SwipeAction -> Ptr SwipeAction -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr SwipeAction
forall a. Ptr a
FP.nullPtr
        then SwipeAction -> Maybe SwipeAction
forall a. a -> Maybe a
P.Just (SwipeAction -> Maybe SwipeAction)
-> IO SwipeAction -> IO (Maybe SwipeAction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr SwipeAction -> SwipeAction)
-> Ptr SwipeAction -> IO SwipeAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SwipeAction -> SwipeAction
SwipeAction Ptr SwipeAction
ptr
        else Maybe SwipeAction -> IO (Maybe SwipeAction)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SwipeAction
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveSwipeActionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveSwipeActionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSwipeActionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSwipeActionMethod "cancel" o = Clutter.GestureAction.GestureActionCancelMethodInfo
    ResolveSwipeActionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSwipeActionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSwipeActionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSwipeActionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSwipeActionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSwipeActionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSwipeActionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSwipeActionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSwipeActionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSwipeActionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSwipeActionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSwipeActionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSwipeActionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSwipeActionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSwipeActionMethod "getActor" o = Clutter.ActorMeta.ActorMetaGetActorMethodInfo
    ResolveSwipeActionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSwipeActionMethod "getDevice" o = Clutter.GestureAction.GestureActionGetDeviceMethodInfo
    ResolveSwipeActionMethod "getEnabled" o = Clutter.ActorMeta.ActorMetaGetEnabledMethodInfo
    ResolveSwipeActionMethod "getLastEvent" o = Clutter.GestureAction.GestureActionGetLastEventMethodInfo
    ResolveSwipeActionMethod "getMotionCoords" o = Clutter.GestureAction.GestureActionGetMotionCoordsMethodInfo
    ResolveSwipeActionMethod "getMotionDelta" o = Clutter.GestureAction.GestureActionGetMotionDeltaMethodInfo
    ResolveSwipeActionMethod "getNCurrentPoints" o = Clutter.GestureAction.GestureActionGetNCurrentPointsMethodInfo
    ResolveSwipeActionMethod "getNTouchPoints" o = Clutter.GestureAction.GestureActionGetNTouchPointsMethodInfo
    ResolveSwipeActionMethod "getName" o = Clutter.ActorMeta.ActorMetaGetNameMethodInfo
    ResolveSwipeActionMethod "getPressCoords" o = Clutter.GestureAction.GestureActionGetPressCoordsMethodInfo
    ResolveSwipeActionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSwipeActionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSwipeActionMethod "getReleaseCoords" o = Clutter.GestureAction.GestureActionGetReleaseCoordsMethodInfo
    ResolveSwipeActionMethod "getSequence" o = Clutter.GestureAction.GestureActionGetSequenceMethodInfo
    ResolveSwipeActionMethod "getThresholdTriggerDistance" o = Clutter.GestureAction.GestureActionGetThresholdTriggerDistanceMethodInfo
    ResolveSwipeActionMethod "getThresholdTriggerEdge" o = Clutter.GestureAction.GestureActionGetThresholdTriggerEdgeMethodInfo
    ResolveSwipeActionMethod "getThresholdTriggerEgde" o = Clutter.GestureAction.GestureActionGetThresholdTriggerEgdeMethodInfo
    ResolveSwipeActionMethod "getVelocity" o = Clutter.GestureAction.GestureActionGetVelocityMethodInfo
    ResolveSwipeActionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSwipeActionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSwipeActionMethod "setEnabled" o = Clutter.ActorMeta.ActorMetaSetEnabledMethodInfo
    ResolveSwipeActionMethod "setNTouchPoints" o = Clutter.GestureAction.GestureActionSetNTouchPointsMethodInfo
    ResolveSwipeActionMethod "setName" o = Clutter.ActorMeta.ActorMetaSetNameMethodInfo
    ResolveSwipeActionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSwipeActionMethod "setThresholdTriggerDistance" o = Clutter.GestureAction.GestureActionSetThresholdTriggerDistanceMethodInfo
    ResolveSwipeActionMethod "setThresholdTriggerEdge" o = Clutter.GestureAction.GestureActionSetThresholdTriggerEdgeMethodInfo
    ResolveSwipeActionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSwipeActionMethod t SwipeAction, O.OverloadedMethod info SwipeAction p) => OL.IsLabel t (SwipeAction -> 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 ~ ResolveSwipeActionMethod t SwipeAction, O.OverloadedMethod info SwipeAction p, R.HasField t SwipeAction p) => R.HasField t SwipeAction p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSwipeActionMethod t SwipeAction, O.OverloadedMethodInfo info SwipeAction) => OL.IsLabel t (O.MethodProxy info SwipeAction) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
{-# DEPRECATED SwipeActionSweptCallback ["(Since version 1.14)","Use the [swipe](#g:signal:swipe) signal instead."] #-}
type SwipeActionSweptCallback =
    Clutter.Actor.Actor
    
    -> [Clutter.Flags.SwipeDirection]
    
    -> IO ()
type C_SwipeActionSweptCallback =
    Ptr SwipeAction ->                      
    Ptr Clutter.Actor.Actor ->
    CUInt ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_SwipeActionSweptCallback :: C_SwipeActionSweptCallback -> IO (FunPtr C_SwipeActionSweptCallback)
wrap_SwipeActionSweptCallback :: 
    GObject a => (a -> SwipeActionSweptCallback) ->
    C_SwipeActionSweptCallback
wrap_SwipeActionSweptCallback :: forall a.
GObject a =>
(a -> SwipeActionSweptCallback) -> C_SwipeActionSweptCallback
wrap_SwipeActionSweptCallback a -> SwipeActionSweptCallback
gi'cb Ptr SwipeAction
gi'selfPtr Ptr Actor
actor CUInt
direction Ptr ()
_ = do
    Actor
actor' <- ((ManagedPtr Actor -> Actor) -> Ptr Actor -> IO Actor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Actor -> Actor
Clutter.Actor.Actor) Ptr Actor
actor
    let direction' :: [SwipeDirection]
direction' = CUInt -> [SwipeDirection]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
direction
    Ptr SwipeAction -> (SwipeAction -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr SwipeAction
gi'selfPtr ((SwipeAction -> IO ()) -> IO ())
-> (SwipeAction -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \SwipeAction
gi'self -> a -> SwipeActionSweptCallback
gi'cb (SwipeAction -> a
forall a b. Coercible a b => a -> b
Coerce.coerce SwipeAction
gi'self)  Actor
actor' [SwipeDirection]
direction'
onSwipeActionSwept :: (IsSwipeAction a, MonadIO m) => a -> ((?self :: a) => SwipeActionSweptCallback) -> m SignalHandlerId
onSwipeActionSwept :: forall a (m :: * -> *).
(IsSwipeAction a, MonadIO m) =>
a -> ((?self::a) => SwipeActionSweptCallback) -> m SignalHandlerId
onSwipeActionSwept a
obj (?self::a) => SwipeActionSweptCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> SwipeActionSweptCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SwipeActionSweptCallback
SwipeActionSweptCallback
cb
    let wrapped' :: C_SwipeActionSweptCallback
wrapped' = (a -> SwipeActionSweptCallback) -> C_SwipeActionSweptCallback
forall a.
GObject a =>
(a -> SwipeActionSweptCallback) -> C_SwipeActionSweptCallback
wrap_SwipeActionSweptCallback a -> SwipeActionSweptCallback
wrapped
    FunPtr C_SwipeActionSweptCallback
wrapped'' <- C_SwipeActionSweptCallback
-> IO (FunPtr C_SwipeActionSweptCallback)
mk_SwipeActionSweptCallback C_SwipeActionSweptCallback
wrapped'
    a
-> Text
-> FunPtr C_SwipeActionSweptCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"swept" FunPtr C_SwipeActionSweptCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSwipeActionSwept :: (IsSwipeAction a, MonadIO m) => a -> ((?self :: a) => SwipeActionSweptCallback) -> m SignalHandlerId
afterSwipeActionSwept :: forall a (m :: * -> *).
(IsSwipeAction a, MonadIO m) =>
a -> ((?self::a) => SwipeActionSweptCallback) -> m SignalHandlerId
afterSwipeActionSwept a
obj (?self::a) => SwipeActionSweptCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> SwipeActionSweptCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SwipeActionSweptCallback
SwipeActionSweptCallback
cb
    let wrapped' :: C_SwipeActionSweptCallback
wrapped' = (a -> SwipeActionSweptCallback) -> C_SwipeActionSweptCallback
forall a.
GObject a =>
(a -> SwipeActionSweptCallback) -> C_SwipeActionSweptCallback
wrap_SwipeActionSweptCallback a -> SwipeActionSweptCallback
wrapped
    FunPtr C_SwipeActionSweptCallback
wrapped'' <- C_SwipeActionSweptCallback
-> IO (FunPtr C_SwipeActionSweptCallback)
mk_SwipeActionSweptCallback C_SwipeActionSweptCallback
wrapped'
    a
-> Text
-> FunPtr C_SwipeActionSweptCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"swept" FunPtr C_SwipeActionSweptCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data SwipeActionSweptSignalInfo
instance SignalInfo SwipeActionSweptSignalInfo where
    type HaskellCallbackType SwipeActionSweptSignalInfo = SwipeActionSweptCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SwipeActionSweptCallback cb
        cb'' <- mk_SwipeActionSweptCallback cb'
        connectSignalFunPtr obj "swept" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.SwipeAction::swept"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-SwipeAction.html#g:signal:swept"})
#endif
type SwipeActionSwipeCallback =
    Clutter.Actor.Actor
    
    -> [Clutter.Flags.SwipeDirection]
    
    -> IO Bool
    
    
type C_SwipeActionSwipeCallback =
    Ptr SwipeAction ->                      
    Ptr Clutter.Actor.Actor ->
    CUInt ->
    Ptr () ->                               
    IO CInt
foreign import ccall "wrapper"
    mk_SwipeActionSwipeCallback :: C_SwipeActionSwipeCallback -> IO (FunPtr C_SwipeActionSwipeCallback)
wrap_SwipeActionSwipeCallback :: 
    GObject a => (a -> SwipeActionSwipeCallback) ->
    C_SwipeActionSwipeCallback
wrap_SwipeActionSwipeCallback :: forall a.
GObject a =>
(a -> SwipeActionSwipeCallback) -> C_SwipeActionSwipeCallback
wrap_SwipeActionSwipeCallback a -> SwipeActionSwipeCallback
gi'cb Ptr SwipeAction
gi'selfPtr Ptr Actor
actor CUInt
direction Ptr ()
_ = do
    Actor
actor' <- ((ManagedPtr Actor -> Actor) -> Ptr Actor -> IO Actor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Actor -> Actor
Clutter.Actor.Actor) Ptr Actor
actor
    let direction' :: [SwipeDirection]
direction' = CUInt -> [SwipeDirection]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
direction
    Bool
result <- Ptr SwipeAction -> (SwipeAction -> IO Bool) -> IO Bool
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr SwipeAction
gi'selfPtr ((SwipeAction -> IO Bool) -> IO Bool)
-> (SwipeAction -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \SwipeAction
gi'self -> a -> SwipeActionSwipeCallback
gi'cb (SwipeAction -> a
forall a b. Coercible a b => a -> b
Coerce.coerce SwipeAction
gi'self)  Actor
actor' [SwipeDirection]
direction'
    let result' :: CInt
result' = (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
result
    CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onSwipeActionSwipe :: (IsSwipeAction a, MonadIO m) => a -> ((?self :: a) => SwipeActionSwipeCallback) -> m SignalHandlerId
onSwipeActionSwipe :: forall a (m :: * -> *).
(IsSwipeAction a, MonadIO m) =>
a -> ((?self::a) => SwipeActionSwipeCallback) -> m SignalHandlerId
onSwipeActionSwipe a
obj (?self::a) => SwipeActionSwipeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> SwipeActionSwipeCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SwipeActionSwipeCallback
SwipeActionSwipeCallback
cb
    let wrapped' :: C_SwipeActionSwipeCallback
wrapped' = (a -> SwipeActionSwipeCallback) -> C_SwipeActionSwipeCallback
forall a.
GObject a =>
(a -> SwipeActionSwipeCallback) -> C_SwipeActionSwipeCallback
wrap_SwipeActionSwipeCallback a -> SwipeActionSwipeCallback
wrapped
    FunPtr C_SwipeActionSwipeCallback
wrapped'' <- C_SwipeActionSwipeCallback
-> IO (FunPtr C_SwipeActionSwipeCallback)
mk_SwipeActionSwipeCallback C_SwipeActionSwipeCallback
wrapped'
    a
-> Text
-> FunPtr C_SwipeActionSwipeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"swipe" FunPtr C_SwipeActionSwipeCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterSwipeActionSwipe :: (IsSwipeAction a, MonadIO m) => a -> ((?self :: a) => SwipeActionSwipeCallback) -> m SignalHandlerId
afterSwipeActionSwipe :: forall a (m :: * -> *).
(IsSwipeAction a, MonadIO m) =>
a -> ((?self::a) => SwipeActionSwipeCallback) -> m SignalHandlerId
afterSwipeActionSwipe a
obj (?self::a) => SwipeActionSwipeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> SwipeActionSwipeCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SwipeActionSwipeCallback
SwipeActionSwipeCallback
cb
    let wrapped' :: C_SwipeActionSwipeCallback
wrapped' = (a -> SwipeActionSwipeCallback) -> C_SwipeActionSwipeCallback
forall a.
GObject a =>
(a -> SwipeActionSwipeCallback) -> C_SwipeActionSwipeCallback
wrap_SwipeActionSwipeCallback a -> SwipeActionSwipeCallback
wrapped
    FunPtr C_SwipeActionSwipeCallback
wrapped'' <- C_SwipeActionSwipeCallback
-> IO (FunPtr C_SwipeActionSwipeCallback)
mk_SwipeActionSwipeCallback C_SwipeActionSwipeCallback
wrapped'
    a
-> Text
-> FunPtr C_SwipeActionSwipeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"swipe" FunPtr C_SwipeActionSwipeCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data SwipeActionSwipeSignalInfo
instance SignalInfo SwipeActionSwipeSignalInfo where
    type HaskellCallbackType SwipeActionSwipeSignalInfo = SwipeActionSwipeCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SwipeActionSwipeCallback cb
        cb'' <- mk_SwipeActionSwipeCallback cb'
        connectSignalFunPtr obj "swipe" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.SwipeAction::swipe"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.5/docs/GI-Clutter-Objects-SwipeAction.html#g:signal:swipe"})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SwipeAction
type instance O.AttributeList SwipeAction = SwipeActionAttributeList
type SwipeActionAttributeList = ('[ '("actor", Clutter.ActorMeta.ActorMetaActorPropertyInfo), '("enabled", Clutter.ActorMeta.ActorMetaEnabledPropertyInfo), '("nTouchPoints", Clutter.GestureAction.GestureActionNTouchPointsPropertyInfo), '("name", Clutter.ActorMeta.ActorMetaNamePropertyInfo), '("thresholdTriggerDistanceX", Clutter.GestureAction.GestureActionThresholdTriggerDistanceXPropertyInfo), '("thresholdTriggerDistanceY", Clutter.GestureAction.GestureActionThresholdTriggerDistanceYPropertyInfo), '("thresholdTriggerEdge", Clutter.GestureAction.GestureActionThresholdTriggerEdgePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SwipeAction = SwipeActionSignalList
type SwipeActionSignalList = ('[ '("gestureBegin", Clutter.GestureAction.GestureActionGestureBeginSignalInfo), '("gestureCancel", Clutter.GestureAction.GestureActionGestureCancelSignalInfo), '("gestureEnd", Clutter.GestureAction.GestureActionGestureEndSignalInfo), '("gestureProgress", Clutter.GestureAction.GestureActionGestureProgressSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("swept", SwipeActionSweptSignalInfo), '("swipe", SwipeActionSwipeSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "clutter_swipe_action_new" clutter_swipe_action_new :: 
    IO (Ptr SwipeAction)
swipeActionNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m SwipeAction
    
swipeActionNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m SwipeAction
swipeActionNew  = IO SwipeAction -> m SwipeAction
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SwipeAction -> m SwipeAction)
-> IO SwipeAction -> m SwipeAction
forall a b. (a -> b) -> a -> b
$ do
    Ptr SwipeAction
result <- IO (Ptr SwipeAction)
clutter_swipe_action_new
    Text -> Ptr SwipeAction -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"swipeActionNew" Ptr SwipeAction
result
    SwipeAction
result' <- ((ManagedPtr SwipeAction -> SwipeAction)
-> Ptr SwipeAction -> IO SwipeAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr SwipeAction -> SwipeAction
SwipeAction) Ptr SwipeAction
result
    SwipeAction -> IO SwipeAction
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SwipeAction
result'
#if defined(ENABLE_OVERLOADING)
#endif