{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.Gtk.Objects.GestureSwipe
    ( 

-- * Exported types
    GestureSwipe(..)                        ,
    GestureSwipeK                           ,
    toGestureSwipe                          ,
    noGestureSwipe                          ,


 -- * Methods
-- ** gestureSwipeGetVelocity
    gestureSwipeGetVelocity                 ,


-- ** gestureSwipeNew
    gestureSwipeNew                         ,




 -- * Signals
-- ** Swipe
    GestureSwipeSwipeCallback               ,
    GestureSwipeSwipeCallbackC              ,
    GestureSwipeSwipeSignalInfo             ,
    afterGestureSwipeSwipe                  ,
    gestureSwipeSwipeCallbackWrapper        ,
    gestureSwipeSwipeClosure                ,
    mkGestureSwipeSwipeCallback             ,
    noGestureSwipeSwipeCallback             ,
    onGestureSwipeSwipe                     ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.GObject as GObject

newtype GestureSwipe = GestureSwipe (ForeignPtr GestureSwipe)
foreign import ccall "gtk_gesture_swipe_get_type"
    c_gtk_gesture_swipe_get_type :: IO GType

type instance ParentTypes GestureSwipe = GestureSwipeParentTypes
type GestureSwipeParentTypes = '[GestureSingle, Gesture, EventController, GObject.Object]

instance GObject GestureSwipe where
    gobjectIsInitiallyUnowned _ = False
    gobjectType _ = c_gtk_gesture_swipe_get_type
    

class GObject o => GestureSwipeK o
instance (GObject o, IsDescendantOf GestureSwipe o) => GestureSwipeK o

toGestureSwipe :: GestureSwipeK o => o -> IO GestureSwipe
toGestureSwipe = unsafeCastTo GestureSwipe

noGestureSwipe :: Maybe GestureSwipe
noGestureSwipe = Nothing

-- signal GestureSwipe::swipe
type GestureSwipeSwipeCallback =
    Double ->
    Double ->
    IO ()

noGestureSwipeSwipeCallback :: Maybe GestureSwipeSwipeCallback
noGestureSwipeSwipeCallback = Nothing

type GestureSwipeSwipeCallbackC =
    Ptr () ->                               -- object
    CDouble ->
    CDouble ->
    Ptr () ->                               -- user_data
    IO ()

foreign import ccall "wrapper"
    mkGestureSwipeSwipeCallback :: GestureSwipeSwipeCallbackC -> IO (FunPtr GestureSwipeSwipeCallbackC)

gestureSwipeSwipeClosure :: GestureSwipeSwipeCallback -> IO Closure
gestureSwipeSwipeClosure cb = newCClosure =<< mkGestureSwipeSwipeCallback wrapped
    where wrapped = gestureSwipeSwipeCallbackWrapper cb

gestureSwipeSwipeCallbackWrapper ::
    GestureSwipeSwipeCallback ->
    Ptr () ->
    CDouble ->
    CDouble ->
    Ptr () ->
    IO ()
gestureSwipeSwipeCallbackWrapper _cb _ velocity_x velocity_y _ = do
    let velocity_x' = realToFrac velocity_x
    let velocity_y' = realToFrac velocity_y
    _cb  velocity_x' velocity_y'

onGestureSwipeSwipe :: (GObject a, MonadIO m) => a -> GestureSwipeSwipeCallback -> m SignalHandlerId
onGestureSwipeSwipe obj cb = liftIO $ connectGestureSwipeSwipe obj cb SignalConnectBefore
afterGestureSwipeSwipe :: (GObject a, MonadIO m) => a -> GestureSwipeSwipeCallback -> m SignalHandlerId
afterGestureSwipeSwipe obj cb = connectGestureSwipeSwipe obj cb SignalConnectAfter

connectGestureSwipeSwipe :: (GObject a, MonadIO m) =>
                            a -> GestureSwipeSwipeCallback -> SignalConnectMode -> m SignalHandlerId
connectGestureSwipeSwipe obj cb after = liftIO $ do
    cb' <- mkGestureSwipeSwipeCallback (gestureSwipeSwipeCallbackWrapper cb)
    connectSignalFunPtr obj "swipe" cb' after

type instance AttributeList GestureSwipe = GestureSwipeAttributeList
type GestureSwipeAttributeList = ('[ '("button", GestureSingleButtonPropertyInfo), '("exclusive", GestureSingleExclusivePropertyInfo), '("n-points", GestureNPointsPropertyInfo), '("propagation-phase", EventControllerPropagationPhasePropertyInfo), '("touch-only", GestureSingleTouchOnlyPropertyInfo), '("widget", EventControllerWidgetPropertyInfo), '("window", GestureWindowPropertyInfo)] :: [(Symbol, *)])

data GestureSwipeSwipeSignalInfo
instance SignalInfo GestureSwipeSwipeSignalInfo where
    type HaskellCallbackType GestureSwipeSwipeSignalInfo = GestureSwipeSwipeCallback
    connectSignal _ = connectGestureSwipeSwipe

type instance SignalList GestureSwipe = GestureSwipeSignalList
type GestureSwipeSignalList = ('[ '("begin", GestureBeginSignalInfo), '("cancel", GestureCancelSignalInfo), '("end", GestureEndSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("sequence-state-changed", GestureSequenceStateChangedSignalInfo), '("swipe", GestureSwipeSwipeSignalInfo), '("update", GestureUpdateSignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])

-- method GestureSwipe::new
-- method type : Constructor
-- Args : [Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "widget", argType = TInterface "Gtk" "Widget", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "GestureSwipe"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_gesture_swipe_new" gtk_gesture_swipe_new :: 
    Ptr Widget ->                           -- widget : TInterface "Gtk" "Widget"
    IO (Ptr GestureSwipe)


gestureSwipeNew ::
    (MonadIO m, WidgetK a) =>
    a ->                                    -- widget
    m GestureSwipe
gestureSwipeNew widget = liftIO $ do
    let widget' = unsafeManagedPtrCastPtr widget
    result <- gtk_gesture_swipe_new widget'
    checkUnexpectedReturnNULL "gtk_gesture_swipe_new" result
    result' <- (wrapObject GestureSwipe) result
    touchManagedPtr widget
    return result'

-- method GestureSwipe::get_velocity
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "GestureSwipe", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "velocity_x", argType = TBasicType TDouble, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "velocity_y", argType = TBasicType TDouble, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "GestureSwipe", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "gtk_gesture_swipe_get_velocity" gtk_gesture_swipe_get_velocity :: 
    Ptr GestureSwipe ->                     -- _obj : TInterface "Gtk" "GestureSwipe"
    Ptr CDouble ->                          -- velocity_x : TBasicType TDouble
    Ptr CDouble ->                          -- velocity_y : TBasicType TDouble
    IO CInt


gestureSwipeGetVelocity ::
    (MonadIO m, GestureSwipeK a) =>
    a ->                                    -- _obj
    m (Bool,Double,Double)
gestureSwipeGetVelocity _obj = liftIO $ do
    let _obj' = unsafeManagedPtrCastPtr _obj
    velocity_x <- allocMem :: IO (Ptr CDouble)
    velocity_y <- allocMem :: IO (Ptr CDouble)
    result <- gtk_gesture_swipe_get_velocity _obj' velocity_x velocity_y
    let result' = (/= 0) result
    velocity_x' <- peek velocity_x
    let velocity_x'' = realToFrac velocity_x'
    velocity_y' <- peek velocity_y
    let velocity_y'' = realToFrac velocity_y'
    touchManagedPtr _obj
    freeMem velocity_x
    freeMem velocity_y
    return (result', velocity_x'', velocity_y'')