module Graphics.UI.Gtk.General.Drag (
  DragContext,
  DragContextClass,
  DragAction(..),
  DestDefaults(..),
  DragProtocol(..),
  DragResult(..),
  castToDragContext, gTypeDragContext,
  toDragContext,
  dragDestSet,
  dragDestSetProxy,
  dragDestUnset,
  dragDestFindTarget,
  dragDestGetTargetList,
  dragDestSetTargetList,
  dragDestAddTextTargets,
  dragDestAddImageTargets,
  dragDestAddURITargets,
  dragStatus,
  dragFinish,
  dragGetData,
  dragGetSourceWidget,
  dragHighlight,
  dragUnhighlight,
  dragSetIconWidget,
  dragSetIconPixbuf,
  dragSetIconStock,
  dragSetIconName,
  dragSetIconDefault,
  dragCheckThreshold,
  dragSourceSet,
  dragSourceSetIconPixbuf,
  dragSourceSetIconStock,
  dragSourceSetIconName,
  dragSourceUnset,
  dragSourceSetTargetList,
  dragSourceGetTargetList,
  dragSourceAddTextTargets,
  dragSourceAddImageTargets,
  dragSourceAddURITargets,
  
  dragBegin,
  dragDataDelete,
  dragDataGet,
  dragDataReceived,
  dragDrop,
  dragEnd,
  dragFailed,
  dragLeave,
  dragMotion
  ) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Flags
import Graphics.UI.Gtk.General.StockItems ( StockId )
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.General.DNDTypes
import Graphics.UI.Gtk.Gdk.Enums ( DragAction(..) )
import Graphics.UI.Gtk.General.Enums ( DestDefaults(..), DragProtocol(..)
                                     , DragResult(..)
                                     )
import Graphics.UI.Gtk.Gdk.Events ( TimeStamp, Modifier )
import Graphics.UI.Gtk.General.Structs ( Point,
  )
import Graphics.UI.Gtk.Signals
import Control.Monad.Reader (runReaderT)
dragDestSet :: WidgetClass widget => widget -> [DestDefaults] -> [DragAction] -> IO ()
dragDestSet widget flags actions =
  (\(Widget arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_dest_set argPtr1 arg2 arg3 arg4 arg5)
    (toWidget widget)
    ((fromIntegral . fromFlags) flags)
    nullPtr 0
    ((fromIntegral . fromFlags) actions)
dragDestSetProxy :: WidgetClass widget => widget
  -> DrawWindow 
  -> DragProtocol 
  -> Bool 
          
  -> IO ()
dragDestSetProxy widget proxyWindow protocol useCoordinates =
  (\(Widget arg1) (DrawWindow arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_drag_dest_set_proxy argPtr1 argPtr2 arg3 arg4)
    (toWidget widget)
    proxyWindow
    ((fromIntegral . fromEnum) protocol)
    (fromBool useCoordinates)
dragDestUnset :: WidgetClass widget => widget -> IO ()
dragDestUnset widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_dest_unset argPtr1)
    (toWidget widget)
dragDestFindTarget :: (WidgetClass widget, DragContextClass context) =>
  widget -> context -> Maybe TargetList -> IO (Maybe TargetTag)
dragDestFindTarget widget context (Just targetList) = do
  ttPtr <-
    (\(Widget arg1) (DragContext arg2) (TargetList arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->gtk_drag_dest_find_target argPtr1 argPtr2 argPtr3)
    (toWidget widget)
    (toDragContext context)
    targetList
  if ttPtr==nullPtr then return Nothing else return (Just (Atom ttPtr))
dragDestFindTarget widget context Nothing = do
  ttPtr <-
    (\(Widget arg1) (DragContext arg2) (TargetList arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->gtk_drag_dest_find_target argPtr1 argPtr2 argPtr3)
    (toWidget widget)
    (toDragContext context)
    (TargetList nullForeignPtr)
  if ttPtr==nullPtr then return Nothing else return (Just (Atom ttPtr))
dragDestGetTargetList :: WidgetClass widget => widget -> IO (Maybe TargetList)
dragDestGetTargetList widget = do
  tlPtr <- (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_dest_get_target_list argPtr1) (toWidget widget)
  if tlPtr==nullPtr then return Nothing else liftM Just (mkTargetList tlPtr)
dragDestSetTargetList :: WidgetClass widget => widget -> TargetList -> IO ()
dragDestSetTargetList widget targetList =
  (\(Widget arg1) (TargetList arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_drag_dest_set_target_list argPtr1 argPtr2)
    (toWidget widget)
    targetList
dragDestAddTextTargets :: WidgetClass widget => widget -> IO ()
dragDestAddTextTargets widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_dest_add_text_targets argPtr1)
    (toWidget widget)
dragDestAddImageTargets :: WidgetClass widget => widget -> IO ()
dragDestAddImageTargets widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_dest_add_image_targets argPtr1)
    (toWidget widget)
dragDestAddURITargets :: WidgetClass widget => widget -> IO ()
dragDestAddURITargets widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_dest_add_uri_targets argPtr1)
    (toWidget widget)
dragFinish :: DragContextClass context => context
  -> Bool 
  -> Bool 
  
  -> TimeStamp 
  -> IO ()
dragFinish context success del time =
  (\(DragContext arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_finish argPtr1 arg2 arg3 arg4)
    (toDragContext context)
    (fromBool success)
    (fromBool del)
    (fromIntegral time)
dragGetData :: (WidgetClass widget, DragContextClass context)
  => widget 
  -> context
  -> TargetTag 
  -> TimeStamp 
               
  -> IO ()
dragGetData widget context (Atom target) time =
  (\(Widget arg1) (DragContext arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_drag_get_data argPtr1 argPtr2 arg3 arg4)
    (toWidget widget)
    (toDragContext context)
    target
    (fromIntegral time)
dragGetSourceWidget :: DragContextClass context => context -> IO (Maybe Widget)
dragGetSourceWidget context =
  maybeNull (makeNewGObject mkWidget) $
    (\(DragContext arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_get_source_widget argPtr1)
    (toDragContext context)
dragHighlight :: WidgetClass widget => widget -> IO ()
dragHighlight widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_highlight argPtr1)
    (toWidget widget)
dragUnhighlight :: WidgetClass widget => widget -> IO ()
dragUnhighlight widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_unhighlight argPtr1)
    (toWidget widget)
dragSetIconWidget :: (DragContextClass context, WidgetClass widget) =>
  context -> widget
  -> Int 
  -> Int 
  -> IO ()
dragSetIconWidget context widget hotX hotY =
  (\(DragContext arg1) (Widget arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_drag_set_icon_widget argPtr1 argPtr2 arg3 arg4)
    (toDragContext context)
    (toWidget widget)
    (fromIntegral hotX)
    (fromIntegral hotY)
dragSetIconPixbuf :: DragContextClass context => context -> Pixbuf
  -> Int 
  -> Int 
  -> IO ()
dragSetIconPixbuf context pixbuf hotX hotY =
  (\(DragContext arg1) (Pixbuf arg2) arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_drag_set_icon_pixbuf argPtr1 argPtr2 arg3 arg4)
    (toDragContext context)
    pixbuf
    (fromIntegral hotX)
    (fromIntegral hotY)
dragSetIconStock :: DragContextClass context => context -> StockId
  -> Int 
  -> Int 
  -> IO ()
dragSetIconStock context stockId hotX hotY =
  withUTFString stockId $ \stockIdPtr ->
  (\(DragContext arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_set_icon_stock argPtr1 arg2 arg3 arg4)
    (toDragContext context)
    stockIdPtr
    (fromIntegral hotX)
    (fromIntegral hotY)
dragSetIconName :: (DragContextClass context, GlibString string) => context
  -> string
  -> Int 
  -> Int 
  -> IO ()
dragSetIconName context iconName hotX hotY =
  withUTFString iconName $ \iconNamePtr ->
  (\(DragContext arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_set_icon_name argPtr1 arg2 arg3 arg4)
    (toDragContext context)
    iconNamePtr
    (fromIntegral hotX)
    (fromIntegral hotY)
dragSetIconDefault :: DragContextClass context => context -> IO ()
dragSetIconDefault context =
  (\(DragContext arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_set_icon_default argPtr1)
    (toDragContext context)
dragCheckThreshold :: WidgetClass widget => widget
                      -> Int 
                      -> Int 
                      -> Int 
                      -> Int 
                      -> IO Bool
dragCheckThreshold widget startX startY currentX currentY =
  liftM toBool $
  (\(Widget arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_check_threshold argPtr1 arg2 arg3 arg4 arg5)
    (toWidget widget)
    (fromIntegral startX)
    (fromIntegral startY)
    (fromIntegral currentX)
    (fromIntegral currentY)
dragSourceSet :: WidgetClass widget => widget -> [Modifier] -> [DragAction] -> IO ()
dragSourceSet widget startButtonMask actions =
  (\(Widget arg1) arg2 arg3 arg4 arg5 -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_source_set argPtr1 arg2 arg3 arg4 arg5)
    (toWidget widget)
    ((fromIntegral . fromFlags) startButtonMask)
    nullPtr
    0
    ((fromIntegral . fromFlags) actions)
dragSourceSetIconPixbuf :: WidgetClass widget => widget -> Pixbuf -> IO ()
dragSourceSetIconPixbuf widget pixbuf =
  (\(Widget arg1) (Pixbuf arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_drag_source_set_icon_pixbuf argPtr1 argPtr2)
    (toWidget widget)
    pixbuf
dragSourceSetIconStock :: WidgetClass widget => widget -> StockId -> IO ()
dragSourceSetIconStock widget stockId =
  withUTFString stockId $ \stockIdPtr ->
  (\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_source_set_icon_stock argPtr1 arg2)
    (toWidget widget)
    stockIdPtr
dragSourceSetIconName :: (WidgetClass widget, GlibString string) => widget -> string -> IO ()
dragSourceSetIconName widget iconName =
  withUTFString iconName $ \iconNamePtr ->
  (\(Widget arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_source_set_icon_name argPtr1 arg2)
    (toWidget widget)
    iconNamePtr
dragSourceUnset :: WidgetClass widget => widget -> IO ()
dragSourceUnset widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_source_unset argPtr1)
    (toWidget widget)
dragSourceSetTargetList :: WidgetClass widget => widget -> TargetList -> IO ()
dragSourceSetTargetList widget targetList =
  (\(Widget arg1) (TargetList arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_drag_source_set_target_list argPtr1 argPtr2)
    (toWidget widget)
    targetList
dragSourceGetTargetList :: WidgetClass widget => widget -> IO (Maybe TargetList)
dragSourceGetTargetList widget = do
  tlPtr <- (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_source_get_target_list argPtr1) (toWidget widget)
  if tlPtr==nullPtr then return Nothing else liftM Just (mkTargetList tlPtr)
dragSourceAddTextTargets :: WidgetClass widget => widget -> IO ()
dragSourceAddTextTargets widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_source_add_text_targets argPtr1)
    (toWidget widget)
dragSourceAddImageTargets :: WidgetClass widget => widget -> IO ()
dragSourceAddImageTargets widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_source_add_image_targets argPtr1)
    (toWidget widget)
dragSourceAddURITargets :: WidgetClass widget => widget -> IO ()
dragSourceAddURITargets widget =
  (\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_drag_source_add_uri_targets argPtr1)
    (toWidget widget)
dragStatus :: DragContext -> Maybe DragAction -> TimeStamp -> IO ()
dragStatus ctxt mAction ts =
  (\(DragContext arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_drag_status argPtr1 arg2 arg3) ctxt (maybe 0 (fromIntegral . fromEnum) mAction)
    (fromIntegral ts)
dragBegin :: WidgetClass self => Signal self (DragContext -> IO ())
dragBegin = Signal (connect_OBJECT__NONE "drag-begin")
dragDataDelete :: WidgetClass self => Signal self (DragContext -> IO ())
dragDataDelete = Signal (connect_OBJECT__NONE "drag-data-delete")
dragDataGet :: WidgetClass self =>
  Signal self (DragContext -> InfoId -> TimeStamp -> SelectionDataM ())
dragDataGet = Signal (\after object handler -> do
      connect_OBJECT_PTR_WORD_WORD__NONE "drag-data-get" after object $
        \ctxt dataPtr info time -> do
        runReaderT (handler ctxt (fromIntegral info) (fromIntegral time)) dataPtr >>
                    return ())
dragDataReceived :: WidgetClass self =>
  Signal self (DragContext -> Point -> InfoId -> TimeStamp -> SelectionDataM ())
dragDataReceived = Signal (\after object handler -> do
  connect_OBJECT_INT_INT_PTR_WORD_WORD__NONE "drag-data-received" after object $
    \ctxt x y dataPtr info time -> do
    runReaderT (handler ctxt (fromIntegral x, fromIntegral y) (fromIntegral info)
               (fromIntegral time)) dataPtr >> return ())
dragDrop :: WidgetClass self =>
  Signal self (DragContext -> Point -> TimeStamp -> IO Bool)
dragDrop = Signal (\after object handler ->
  connect_OBJECT_INT_INT_WORD__BOOL "drag-drop" after object $ \ctxt x y time ->
    handler ctxt (fromIntegral x, fromIntegral y) (fromIntegral time))
dragEnd :: WidgetClass self => Signal self (DragContext -> IO ())
dragEnd = Signal (connect_OBJECT__NONE "drag-end")
dragFailed :: WidgetClass self => Signal self (DragContext -> DragResult -> IO Bool)
dragFailed = Signal (connect_OBJECT_ENUM__BOOL "drag-failed")
dragLeave :: WidgetClass self => Signal self (DragContext -> TimeStamp -> IO ())
dragLeave = Signal (\after object handler ->
  connect_OBJECT_WORD__NONE "drag-leave" after object $ \ctxt time ->
    handler ctxt (fromIntegral time))
dragMotion :: WidgetClass self =>
  Signal self (DragContext -> Point -> TimeStamp -> IO Bool)
dragMotion = Signal (\after object handler -> do
  connect_OBJECT_INT_INT_WORD__BOOL "drag-motion" after object $ \ctxt x y time ->
    handler ctxt (fromIntegral x, fromIntegral y) (fromIntegral time))
foreign import ccall safe "gtk_drag_dest_set"
  gtk_drag_dest_set :: ((Ptr Widget) -> (CInt -> ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))))
foreign import ccall safe "gtk_drag_dest_set_proxy"
  gtk_drag_dest_set_proxy :: ((Ptr Widget) -> ((Ptr DrawWindow) -> (CInt -> (CInt -> (IO ())))))
foreign import ccall safe "gtk_drag_dest_unset"
  gtk_drag_dest_unset :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_dest_find_target"
  gtk_drag_dest_find_target :: ((Ptr Widget) -> ((Ptr DragContext) -> ((Ptr TargetList) -> (IO (Ptr ())))))
foreign import ccall safe "gtk_drag_dest_get_target_list"
  gtk_drag_dest_get_target_list :: ((Ptr Widget) -> (IO (Ptr TargetList)))
foreign import ccall safe "gtk_drag_dest_set_target_list"
  gtk_drag_dest_set_target_list :: ((Ptr Widget) -> ((Ptr TargetList) -> (IO ())))
foreign import ccall safe "gtk_drag_dest_add_text_targets"
  gtk_drag_dest_add_text_targets :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_dest_add_image_targets"
  gtk_drag_dest_add_image_targets :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_dest_add_uri_targets"
  gtk_drag_dest_add_uri_targets :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_finish"
  gtk_drag_finish :: ((Ptr DragContext) -> (CInt -> (CInt -> (CUInt -> (IO ())))))
foreign import ccall safe "gtk_drag_get_data"
  gtk_drag_get_data :: ((Ptr Widget) -> ((Ptr DragContext) -> ((Ptr ()) -> (CUInt -> (IO ())))))
foreign import ccall safe "gtk_drag_get_source_widget"
  gtk_drag_get_source_widget :: ((Ptr DragContext) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_drag_highlight"
  gtk_drag_highlight :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_unhighlight"
  gtk_drag_unhighlight :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_set_icon_widget"
  gtk_drag_set_icon_widget :: ((Ptr DragContext) -> ((Ptr Widget) -> (CInt -> (CInt -> (IO ())))))
foreign import ccall safe "gtk_drag_set_icon_pixbuf"
  gtk_drag_set_icon_pixbuf :: ((Ptr DragContext) -> ((Ptr Pixbuf) -> (CInt -> (CInt -> (IO ())))))
foreign import ccall safe "gtk_drag_set_icon_stock"
  gtk_drag_set_icon_stock :: ((Ptr DragContext) -> ((Ptr CChar) -> (CInt -> (CInt -> (IO ())))))
foreign import ccall safe "gtk_drag_set_icon_name"
  gtk_drag_set_icon_name :: ((Ptr DragContext) -> ((Ptr CChar) -> (CInt -> (CInt -> (IO ())))))
foreign import ccall safe "gtk_drag_set_icon_default"
  gtk_drag_set_icon_default :: ((Ptr DragContext) -> (IO ()))
foreign import ccall safe "gtk_drag_check_threshold"
  gtk_drag_check_threshold :: ((Ptr Widget) -> (CInt -> (CInt -> (CInt -> (CInt -> (IO CInt))))))
foreign import ccall safe "gtk_drag_source_set"
  gtk_drag_source_set :: ((Ptr Widget) -> (CInt -> ((Ptr ()) -> (CInt -> (CInt -> (IO ()))))))
foreign import ccall safe "gtk_drag_source_set_icon_pixbuf"
  gtk_drag_source_set_icon_pixbuf :: ((Ptr Widget) -> ((Ptr Pixbuf) -> (IO ())))
foreign import ccall safe "gtk_drag_source_set_icon_stock"
  gtk_drag_source_set_icon_stock :: ((Ptr Widget) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_drag_source_set_icon_name"
  gtk_drag_source_set_icon_name :: ((Ptr Widget) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_drag_source_unset"
  gtk_drag_source_unset :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_source_set_target_list"
  gtk_drag_source_set_target_list :: ((Ptr Widget) -> ((Ptr TargetList) -> (IO ())))
foreign import ccall safe "gtk_drag_source_get_target_list"
  gtk_drag_source_get_target_list :: ((Ptr Widget) -> (IO (Ptr TargetList)))
foreign import ccall safe "gtk_drag_source_add_text_targets"
  gtk_drag_source_add_text_targets :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_source_add_image_targets"
  gtk_drag_source_add_image_targets :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gtk_drag_source_add_uri_targets"
  gtk_drag_source_add_uri_targets :: ((Ptr Widget) -> (IO ()))
foreign import ccall safe "gdk_drag_status"
  gdk_drag_status :: ((Ptr DragContext) -> (CInt -> (CUInt -> (IO ()))))