{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Clutter.Objects.TapAction.TapAction' structure contains
-- only private data and should be accessed using the provided API
-- 
-- /Since: 1.14/

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

module GI.Clutter.Objects.TapAction
    ( 

-- * Exported types
    TapAction(..)                           ,
    IsTapAction                             ,
    toTapAction                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [cancel]("GI.Clutter.Objects.GestureAction#g:method:cancel"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getActor]("GI.Clutter.Objects.ActorMeta#g:method:getActor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDevice]("GI.Clutter.Objects.GestureAction#g:method:getDevice"), [getEnabled]("GI.Clutter.Objects.ActorMeta#g:method:getEnabled"), [getLastEvent]("GI.Clutter.Objects.GestureAction#g:method:getLastEvent"), [getMotionCoords]("GI.Clutter.Objects.GestureAction#g:method:getMotionCoords"), [getMotionDelta]("GI.Clutter.Objects.GestureAction#g:method:getMotionDelta"), [getNCurrentPoints]("GI.Clutter.Objects.GestureAction#g:method:getNCurrentPoints"), [getNTouchPoints]("GI.Clutter.Objects.GestureAction#g:method:getNTouchPoints"), [getName]("GI.Clutter.Objects.ActorMeta#g:method:getName"), [getPressCoords]("GI.Clutter.Objects.GestureAction#g:method:getPressCoords"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getReleaseCoords]("GI.Clutter.Objects.GestureAction#g:method:getReleaseCoords"), [getSequence]("GI.Clutter.Objects.GestureAction#g:method:getSequence"), [getThresholdTriggerDistance]("GI.Clutter.Objects.GestureAction#g:method:getThresholdTriggerDistance"), [getThresholdTriggerEdge]("GI.Clutter.Objects.GestureAction#g:method:getThresholdTriggerEdge"), [getThresholdTriggerEgde]("GI.Clutter.Objects.GestureAction#g:method:getThresholdTriggerEgde"), [getVelocity]("GI.Clutter.Objects.GestureAction#g:method:getVelocity").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setEnabled]("GI.Clutter.Objects.ActorMeta#g:method:setEnabled"), [setNTouchPoints]("GI.Clutter.Objects.GestureAction#g:method:setNTouchPoints"), [setName]("GI.Clutter.Objects.ActorMeta#g:method:setName"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setThresholdTriggerDistance]("GI.Clutter.Objects.GestureAction#g:method:setThresholdTriggerDistance"), [setThresholdTriggerEdge]("GI.Clutter.Objects.GestureAction#g:method:setThresholdTriggerEdge").

#if defined(ENABLE_OVERLOADING)
    ResolveTapActionMethod                  ,
#endif

-- ** new #method:new#

    tapActionNew                            ,




 -- * Signals


-- ** tap #signal:tap#

    TapActionTapCallback                    ,
#if defined(ENABLE_OVERLOADING)
    TapActionTapSignalInfo                  ,
#endif
    afterTapActionTap                       ,
    onTapActionTap                          ,




    ) 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.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

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

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

foreign import ccall "clutter_tap_action_get_type"
    c_clutter_tap_action_get_type :: IO B.Types.GType

instance B.Types.TypedObject TapAction where
    glibType :: IO GType
glibType = IO GType
c_clutter_tap_action_get_type

instance B.Types.GObject TapAction

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

instance O.HasParentTypes TapAction
type instance O.ParentTypes TapAction = '[Clutter.GestureAction.GestureAction, Clutter.Action.Action, Clutter.ActorMeta.ActorMeta, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveTapActionMethod (t :: Symbol) (o :: *) :: * where
    ResolveTapActionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTapActionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTapActionMethod "cancel" o = Clutter.GestureAction.GestureActionCancelMethodInfo
    ResolveTapActionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTapActionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTapActionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTapActionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTapActionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTapActionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTapActionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTapActionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTapActionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTapActionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTapActionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTapActionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTapActionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTapActionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTapActionMethod "getActor" o = Clutter.ActorMeta.ActorMetaGetActorMethodInfo
    ResolveTapActionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTapActionMethod "getDevice" o = Clutter.GestureAction.GestureActionGetDeviceMethodInfo
    ResolveTapActionMethod "getEnabled" o = Clutter.ActorMeta.ActorMetaGetEnabledMethodInfo
    ResolveTapActionMethod "getLastEvent" o = Clutter.GestureAction.GestureActionGetLastEventMethodInfo
    ResolveTapActionMethod "getMotionCoords" o = Clutter.GestureAction.GestureActionGetMotionCoordsMethodInfo
    ResolveTapActionMethod "getMotionDelta" o = Clutter.GestureAction.GestureActionGetMotionDeltaMethodInfo
    ResolveTapActionMethod "getNCurrentPoints" o = Clutter.GestureAction.GestureActionGetNCurrentPointsMethodInfo
    ResolveTapActionMethod "getNTouchPoints" o = Clutter.GestureAction.GestureActionGetNTouchPointsMethodInfo
    ResolveTapActionMethod "getName" o = Clutter.ActorMeta.ActorMetaGetNameMethodInfo
    ResolveTapActionMethod "getPressCoords" o = Clutter.GestureAction.GestureActionGetPressCoordsMethodInfo
    ResolveTapActionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTapActionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTapActionMethod "getReleaseCoords" o = Clutter.GestureAction.GestureActionGetReleaseCoordsMethodInfo
    ResolveTapActionMethod "getSequence" o = Clutter.GestureAction.GestureActionGetSequenceMethodInfo
    ResolveTapActionMethod "getThresholdTriggerDistance" o = Clutter.GestureAction.GestureActionGetThresholdTriggerDistanceMethodInfo
    ResolveTapActionMethod "getThresholdTriggerEdge" o = Clutter.GestureAction.GestureActionGetThresholdTriggerEdgeMethodInfo
    ResolveTapActionMethod "getThresholdTriggerEgde" o = Clutter.GestureAction.GestureActionGetThresholdTriggerEgdeMethodInfo
    ResolveTapActionMethod "getVelocity" o = Clutter.GestureAction.GestureActionGetVelocityMethodInfo
    ResolveTapActionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTapActionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTapActionMethod "setEnabled" o = Clutter.ActorMeta.ActorMetaSetEnabledMethodInfo
    ResolveTapActionMethod "setNTouchPoints" o = Clutter.GestureAction.GestureActionSetNTouchPointsMethodInfo
    ResolveTapActionMethod "setName" o = Clutter.ActorMeta.ActorMetaSetNameMethodInfo
    ResolveTapActionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTapActionMethod "setThresholdTriggerDistance" o = Clutter.GestureAction.GestureActionSetThresholdTriggerDistanceMethodInfo
    ResolveTapActionMethod "setThresholdTriggerEdge" o = Clutter.GestureAction.GestureActionSetThresholdTriggerEdgeMethodInfo
    ResolveTapActionMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- signal TapAction::tap
-- | The [tap](#g:signal:tap) signal is emitted when the tap gesture is complete.
-- 
-- /Since: 1.14/
type TapActionTapCallback =
    Clutter.Actor.Actor
    -- ^ /@actor@/: the t'GI.Clutter.Objects.Actor.Actor' attached to the /@action@/
    -> IO ()

type C_TapActionTapCallback =
    Ptr TapAction ->                        -- object
    Ptr Clutter.Actor.Actor ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_TapActionTapCallback`.
foreign import ccall "wrapper"
    mk_TapActionTapCallback :: C_TapActionTapCallback -> IO (FunPtr C_TapActionTapCallback)

wrap_TapActionTapCallback :: 
    GObject a => (a -> TapActionTapCallback) ->
    C_TapActionTapCallback
wrap_TapActionTapCallback :: forall a.
GObject a =>
(a -> TapActionTapCallback) -> C_TapActionTapCallback
wrap_TapActionTapCallback a -> TapActionTapCallback
gi'cb Ptr TapAction
gi'selfPtr Ptr Actor
actor 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
    Ptr TapAction -> (TapAction -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr TapAction
gi'selfPtr ((TapAction -> IO ()) -> IO ()) -> (TapAction -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \TapAction
gi'self -> a -> TapActionTapCallback
gi'cb (TapAction -> a
forall a b. Coercible a b => a -> b
Coerce.coerce TapAction
gi'self)  Actor
actor'


-- | Connect a signal handler for the [tap](#signal:tap) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' tapAction #tap callback
-- @
-- 
-- 
onTapActionTap :: (IsTapAction a, MonadIO m) => a -> ((?self :: a) => TapActionTapCallback) -> m SignalHandlerId
onTapActionTap :: forall a (m :: * -> *).
(IsTapAction a, MonadIO m) =>
a -> ((?self::a) => TapActionTapCallback) -> m SignalHandlerId
onTapActionTap a
obj (?self::a) => TapActionTapCallback
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 -> TapActionTapCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => TapActionTapCallback
TapActionTapCallback
cb
    let wrapped' :: C_TapActionTapCallback
wrapped' = (a -> TapActionTapCallback) -> C_TapActionTapCallback
forall a.
GObject a =>
(a -> TapActionTapCallback) -> C_TapActionTapCallback
wrap_TapActionTapCallback a -> TapActionTapCallback
wrapped
    FunPtr C_TapActionTapCallback
wrapped'' <- C_TapActionTapCallback -> IO (FunPtr C_TapActionTapCallback)
mk_TapActionTapCallback C_TapActionTapCallback
wrapped'
    a
-> Text
-> FunPtr C_TapActionTapCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"tap" FunPtr C_TapActionTapCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [tap](#signal:tap) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' tapAction #tap callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterTapActionTap :: (IsTapAction a, MonadIO m) => a -> ((?self :: a) => TapActionTapCallback) -> m SignalHandlerId
afterTapActionTap :: forall a (m :: * -> *).
(IsTapAction a, MonadIO m) =>
a -> ((?self::a) => TapActionTapCallback) -> m SignalHandlerId
afterTapActionTap a
obj (?self::a) => TapActionTapCallback
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 -> TapActionTapCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => TapActionTapCallback
TapActionTapCallback
cb
    let wrapped' :: C_TapActionTapCallback
wrapped' = (a -> TapActionTapCallback) -> C_TapActionTapCallback
forall a.
GObject a =>
(a -> TapActionTapCallback) -> C_TapActionTapCallback
wrap_TapActionTapCallback a -> TapActionTapCallback
wrapped
    FunPtr C_TapActionTapCallback
wrapped'' <- C_TapActionTapCallback -> IO (FunPtr C_TapActionTapCallback)
mk_TapActionTapCallback C_TapActionTapCallback
wrapped'
    a
-> Text
-> FunPtr C_TapActionTapCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"tap" FunPtr C_TapActionTapCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data TapActionTapSignalInfo
instance SignalInfo TapActionTapSignalInfo where
    type HaskellCallbackType TapActionTapSignalInfo = TapActionTapCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_TapActionTapCallback cb
        cb'' <- mk_TapActionTapCallback cb'
        connectSignalFunPtr obj "tap" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Clutter.Objects.TapAction::tap"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-clutter-1.0.3/docs/GI-Clutter-Objects-TapAction.html#g:signal:tap"})

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TapAction
type instance O.AttributeList TapAction = TapActionAttributeList
type TapActionAttributeList = ('[ '("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, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TapAction = TapActionSignalList
type TapActionSignalList = ('[ '("gestureBegin", Clutter.GestureAction.GestureActionGestureBeginSignalInfo), '("gestureCancel", Clutter.GestureAction.GestureActionGestureCancelSignalInfo), '("gestureEnd", Clutter.GestureAction.GestureActionGestureEndSignalInfo), '("gestureProgress", Clutter.GestureAction.GestureActionGestureProgressSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("tap", TapActionTapSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "clutter_tap_action_new" clutter_tap_action_new :: 
    IO (Ptr TapAction)

-- | Creates a new t'GI.Clutter.Objects.TapAction.TapAction' instance
-- 
-- /Since: 1.14/
tapActionNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m TapAction
    -- ^ __Returns:__ the newly created t'GI.Clutter.Objects.TapAction.TapAction'
tapActionNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m TapAction
tapActionNew  = IO TapAction -> m TapAction
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TapAction -> m TapAction) -> IO TapAction -> m TapAction
forall a b. (a -> b) -> a -> b
$ do
    Ptr TapAction
result <- IO (Ptr TapAction)
clutter_tap_action_new
    Text -> Ptr TapAction -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"tapActionNew" Ptr TapAction
result
    TapAction
result' <- ((ManagedPtr TapAction -> TapAction)
-> Ptr TapAction -> IO TapAction
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TapAction -> TapAction
TapAction) Ptr TapAction
result
    TapAction -> IO TapAction
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TapAction
result'

#if defined(ENABLE_OVERLOADING)
#endif