Maintainer | gtk2hs-users@lists.sourceforge.net Stability : provisional |
---|---|
Portability | portable (depends on GHC) |
Safe Haskell | None |
Language | Haskell98 |
Drag-and-Drop functionality.
GTK+ has a rich set of functions for doing inter-process communication via
the drag-and-drop metaphor. GTK+ can do drag-and-drop (DND) via multiple
protocols. The currently supported protocols are the Xdnd and Motif
protocols. As well as the functions listed here, applications may need to
use some facilities provided for Selection
s. Also, the Drag and Drop API
makes use of signals in the Widget
class.
- data DragContext
- class GObjectClass o => DragContextClass o
- data DragAction
- data DestDefaults
- data DragProtocol
- data DragResult
- castToDragContext :: GObjectClass obj => obj -> DragContext
- gTypeDragContext :: GType
- toDragContext :: DragContextClass o => o -> DragContext
- dragContextActions :: Attr DragContext [DragAction]
- dragContextSuggestedAction :: Attr DragContext DragAction
- dragContextAction :: Attr DragContext DragAction
- dragDestSet :: WidgetClass widget => widget -> [DestDefaults] -> [DragAction] -> IO ()
- dragDestSetProxy :: WidgetClass widget => widget -> DrawWindow -> DragProtocol -> Bool -> IO ()
- dragDestUnset :: WidgetClass widget => widget -> IO ()
- dragDestFindTarget :: (WidgetClass widget, DragContextClass context) => widget -> context -> Maybe TargetList -> IO (Maybe TargetTag)
- dragDestGetTargetList :: WidgetClass widget => widget -> IO (Maybe TargetList)
- dragDestSetTargetList :: WidgetClass widget => widget -> TargetList -> IO ()
- dragDestAddTextTargets :: WidgetClass widget => widget -> IO ()
- dragDestAddImageTargets :: WidgetClass widget => widget -> IO ()
- dragDestAddURITargets :: WidgetClass widget => widget -> IO ()
- dragStatus :: DragContext -> Maybe DragAction -> TimeStamp -> IO ()
- dragFinish :: DragContextClass context => context -> Bool -> Bool -> TimeStamp -> IO ()
- dragGetData :: (WidgetClass widget, DragContextClass context) => widget -> context -> TargetTag -> TimeStamp -> IO ()
- dragGetSourceWidget :: DragContextClass context => context -> IO (Maybe Widget)
- dragHighlight :: WidgetClass widget => widget -> IO ()
- dragUnhighlight :: WidgetClass widget => widget -> IO ()
- dragSetIconWidget :: (DragContextClass context, WidgetClass widget) => context -> widget -> Int -> Int -> IO ()
- dragSetIconPixbuf :: DragContextClass context => context -> Pixbuf -> Int -> Int -> IO ()
- dragSetIconStock :: DragContextClass context => context -> StockId -> Int -> Int -> IO ()
- dragSetIconName :: (DragContextClass context, GlibString string) => context -> string -> Int -> Int -> IO ()
- dragSetIconDefault :: DragContextClass context => context -> IO ()
- dragCheckThreshold :: WidgetClass widget => widget -> Int -> Int -> Int -> Int -> IO Bool
- dragSourceSet :: WidgetClass widget => widget -> [Modifier] -> [DragAction] -> IO ()
- dragSourceSetIconPixbuf :: WidgetClass widget => widget -> Pixbuf -> IO ()
- dragSourceSetIconStock :: WidgetClass widget => widget -> StockId -> IO ()
- dragSourceSetIconName :: (WidgetClass widget, GlibString string) => widget -> string -> IO ()
- dragSourceUnset :: WidgetClass widget => widget -> IO ()
- dragSourceSetTargetList :: WidgetClass widget => widget -> TargetList -> IO ()
- dragSourceGetTargetList :: WidgetClass widget => widget -> IO (Maybe TargetList)
- dragSourceAddTextTargets :: WidgetClass widget => widget -> IO ()
- dragSourceAddImageTargets :: WidgetClass widget => widget -> IO ()
- dragSourceAddURITargets :: WidgetClass widget => widget -> IO ()
- dragBegin :: WidgetClass self => Signal self (DragContext -> IO ())
- dragDataDelete :: WidgetClass self => Signal self (DragContext -> IO ())
- dragDataGet :: WidgetClass self => Signal self (DragContext -> InfoId -> TimeStamp -> SelectionDataM ())
- dragDataReceived :: WidgetClass self => Signal self (DragContext -> Point -> InfoId -> TimeStamp -> SelectionDataM ())
- dragDrop :: WidgetClass self => Signal self (DragContext -> Point -> TimeStamp -> IO Bool)
- dragEnd :: WidgetClass self => Signal self (DragContext -> IO ())
- dragFailed :: WidgetClass self => Signal self (DragContext -> DragResult -> IO Bool)
- dragLeave :: WidgetClass self => Signal self (DragContext -> TimeStamp -> IO ())
- dragMotion :: WidgetClass self => Signal self (DragContext -> Point -> TimeStamp -> IO Bool)
Types
data DragContext Source #
class GObjectClass o => DragContextClass o Source #
data DragAction Source #
Used in DragContext
to indicate what the
destination should do with the dropped data.
ActionDefault
: Initialisation value, should not be used.ActionCopy
: Copy the data.ActionMove
: Move the data, i.e. first copy it, then delete it from the source.ActionLink
: Add a link to the data. Note that this is only useful if source and destination agree on what it means.ActionPrivate
: Special action which tells the source that the destination will do something that the source doesn't understand.ActionAsk
: Ask the user what to do with the data.
Bounded DragAction Source # | |
Enum DragAction Source # | Specify how to dither colors onto the screen. Removed in Gtk3. |
Eq DragAction Source # | |
Show DragAction Source # | |
Flags DragAction Source # | |
data DestDefaults Source #
The DestDefaults
enumeration specifies the various types of action that
will be taken on behalf of the user for a drag destination site.
DestDefaultMotion
: If set for a widget, GTK+, during a drag over this widget will check if the drag matches this widget's list of possible targets and actions. GTK+ will then calldragStatus
as appropriate.DestDefaultHighlight
: If set for a widget, GTK+ will draw a highlight on this widget as long as a drag is over this widget and the widget drag format and action are acceptable.DestDefaultDrop
: If set for a widget, when a drop occurs, GTK+ will will check if the drag matches this widget's list of possible targets and actions. If so, GTK+ will calldragGetData
on behalf of the widget. Whether or not the drop is successful, GTK+ will calldragFinish
. If the action was a move, then if the drag was successful, thenTrue
will be passed for the delete parameter todragFinish
DestDefaultAll
: If set, specifies that all default actions should be taken.
Bounded DestDefaults Source # | |
Enum DestDefaults Source # | Gives an indication why a drag operation failed. The value can by
obtained by connecting to the
|
Eq DestDefaults Source # | |
Show DestDefaults Source # | |
Flags DestDefaults Source # | |
data DragProtocol Source #
Used in DragContext
to indicate the protocol according to which DND is done.
data DragResult Source #
castToDragContext :: GObjectClass obj => obj -> DragContext Source #
toDragContext :: DragContextClass o => o -> DragContext Source #
Methods
dragContextActions :: Attr DragContext [DragAction] Source #
A set of actions that the source recommends to be taken. Only valid if
dragContextSuggestedAction
is set to ActionAsk
.
Removed in Gtk3.
dragContextSuggestedAction :: Attr DragContext DragAction Source #
The action suggested by the source.
dragContextAction :: Attr DragContext DragAction Source #
The action chosen by the destination.
dragDestSet :: WidgetClass widget => widget -> [DestDefaults] -> [DragAction] -> IO () Source #
Sets a widget as a potential drop destination.
- The
DestDefaults
flags specify what actions Gtk should take on behalf of a widget for drops onto that widget. The given actions and any targets set throughdragDestSetTargetList
only are used ifDestDefaultMotion
orDestDefaultDrop
are given. - Things become more complicated when you try to preview the dragged data,
as described in the documentation for
dragMotion
. The default behaviors described by flags make some assumptions, that can conflict with your own signal handlers. For instanceDestDefaultDrop
causes invocations ofdragStatus
in the handler ofdragMotion
, and invocations ofdragFinish
indragDataReceived
. Especially the latter is dramatic, when your owndragMotion
handler callsdragGetData
to inspect the dragged data.
:: WidgetClass widget | |
=> widget | |
-> DrawWindow | The window to which to forward drag events. |
-> DragProtocol | The drag protocol which the |
-> Bool | If |
-> IO () |
Sets this widget as a proxy for drops to another window.
dragDestUnset :: WidgetClass widget => widget -> IO () Source #
Clears information about a drop destination set with dragDestSet
. The
widget will no longer receive notification of drags.
dragDestFindTarget :: (WidgetClass widget, DragContextClass context) => widget -> context -> Maybe TargetList -> IO (Maybe TargetTag) Source #
Looks for a match between the targets mentioned in the context and the
TargetList
, returning the first matching target, otherwise returning
Nothing
. If Nothing
is given as target list, use the value from
destGetTargetList
. Some widgets may have different valid targets for
different parts of the widget; in that case, they will have to implement a
dragMotion
handler that passes the correct target list to this
function.
dragDestGetTargetList :: WidgetClass widget => widget -> IO (Maybe TargetList) Source #
Returns the list of targets this widget can accept for drag-and-drop.
dragDestSetTargetList :: WidgetClass widget => widget -> TargetList -> IO () Source #
Sets the target types that this widget can accept from drag-and-drop. The
widget must first be made into a drag destination with dragDestSet
.
dragDestAddTextTargets :: WidgetClass widget => widget -> IO () Source #
Add the text targets supported by the selection mechanism to the target
list of the drag source. The targets are added with an InfoId
of 0. If
you need another value, use targetListAddTextTargets
and
dragSourceSetTargetList
.
dragDestAddImageTargets :: WidgetClass widget => widget -> IO () Source #
Add image targets supported by the selection mechanism to the target list
of the drag source. The targets are added with an InfoId
of 0. If you
need another value, use
targetListAddTextTargets
and
dragSourceSetTargetList
.
dragDestAddURITargets :: WidgetClass widget => widget -> IO () Source #
Add URI targets supported by the selection mechanism to the target list
of the drag source. The targets are added with an InfoId
of 0. If you
need another value, use
targetListAddTextTargets
and
dragSourceSetTargetList
.
dragStatus :: DragContext -> Maybe DragAction -> TimeStamp -> IO () Source #
Visualises the actions offered by the drag source.
- This function is called by the drag destination in response to
dragMotion
called by the drag source. The passed-in action is indicated whereNothing
will show that the drop is not allowed.
:: DragContextClass context | |
=> context | |
-> Bool | a flag indicating whether the drop was successful |
-> Bool | a flag indicating whether the source should delete the original data.
(This should be |
-> TimeStamp | the timestamp from the |
-> IO () |
Informs the drag source that the drop is finished, and that the data of the drag will no longer be required.
:: (WidgetClass widget, DragContextClass context) | |
=> widget | The widget that will receive the |
-> context | |
-> TargetTag | The target (form of the data) to retrieve. |
-> TimeStamp | A timestamp for retrieving the data. This will generally be
the time received in a |
-> IO () |
Gets the data associated with a drag. When the data is received or the
retrieval fails, GTK+ will emit a dragDataReceived
signal. Failure of
the retrieval is indicated by passing Nothing
in the selectionData
signal.
However, when dragGetData
is called
implicitely because the DestDefaultDrop
was set, then the widget will
not receive notification of failed drops.
dragGetSourceWidget :: DragContextClass context => context -> IO (Maybe Widget) Source #
Queries he source widget for a drag.
- If the drag is occurring within a single application, a pointer to the
source widget is returned. Otherwise the return value is
Nothing
.
dragHighlight :: WidgetClass widget => widget -> IO () Source #
Draws a highlight around a widget. This will attach handlers to
the expose handlers, so the highlight will continue to be displayed
until dragUnhighlight
is called.
dragUnhighlight :: WidgetClass widget => widget -> IO () Source #
Removes a highlight set by dragHighlight
from a widget.
:: (DragContextClass context, WidgetClass widget) | |
=> context | |
-> widget | |
-> Int | x hot-spot |
-> Int | y hot-spot |
-> IO () |
Changes the icon for a drag to a given widget. GTK+ will not destroy
the widget, so if you don't want it to persist, you should connect to the
dragEnd
signal and destroy it yourself.
- The function must be called with the context of the source side.
:: DragContextClass context | |
=> context | |
-> Pixbuf | |
-> Int | x hot-spot |
-> Int | y hot-spot |
-> IO () |
Set the given Pixbuf
as the icon for the given drag.
:: DragContextClass context | |
=> context | |
-> StockId | |
-> Int | x hot-spot |
-> Int | y hot-spot |
-> IO () |
Sets the icon for a given drag from a stock ID.
:: (DragContextClass context, GlibString string) | |
=> context | |
-> string | |
-> Int | x hot-spot |
-> Int | y hot-spot |
-> IO () |
Sets the icon for a given drag from a named themed icon. See the docs for
IconTheme
for more details. Note that the size of the icon depends on the
icon theme (the icon is loaded at the DND size), thus x and y hot-spots
have to be used with care. Since Gtk 2.8.
dragSetIconDefault :: DragContextClass context => context -> IO () Source #
Sets the icon for a particular drag to the default icon. This function must be called with a context for the source side of a drag
Checks to see if a mouse drag starting at (startX, startY)
and ending
at (currentX, currenty)
has passed the GTK+ drag threshold, and thus
should trigger the beginning of a drag-and-drop operation.
dragSourceSet :: WidgetClass widget => widget -> [Modifier] -> [DragAction] -> IO () Source #
Sets up a widget so that GTK+ will start a drag operation when the user clicks and drags on the widget. The widget must have a window. Note that a set of possible targets have to be set for a drag to be successful.
dragSourceSetIconPixbuf :: WidgetClass widget => widget -> Pixbuf -> IO () Source #
Sets the icon that will be used for drags from a particular widget from a
Pixbuf
.
dragSourceSetIconStock :: WidgetClass widget => widget -> StockId -> IO () Source #
Sets the icon that will be used for drags from a particular source to a stock icon.
dragSourceSetIconName :: (WidgetClass widget, GlibString string) => widget -> string -> IO () Source #
Sets the icon that will be used for drags from a particular source to a
themed icon. See the docs for IconTheme
for more details.
dragSourceUnset :: WidgetClass widget => widget -> IO () Source #
Undoes the effects of dragSourceSet
.
dragSourceSetTargetList :: WidgetClass widget => widget -> TargetList -> IO () Source #
Changes the target types that this widget offers for drag-and-drop. The
widget must first be made into a drag source with dragSourceSet
.
- Since Gtk 2.4.
dragSourceGetTargetList :: WidgetClass widget => widget -> IO (Maybe TargetList) Source #
Gets the list of targets this widget can provide for drag-and-drop.
- Since Gtk 2.4.
dragSourceAddTextTargets :: WidgetClass widget => widget -> IO () Source #
Add the text targets supported by
Selection
to the target list of
the drag source. The targets are added with info = 0
. If you need
another value, use
targetListAddTextTargets
and
dragSourceSetTargetList
.
- Since Gtk 2.6.
dragSourceAddImageTargets :: WidgetClass widget => widget -> IO () Source #
Add the image targets supported by Selection
to the target list of the
drag source. The targets are added with info = 0
. If you need another
value, use targetListAddTextTargets
and dragSourceSetTargetList
.
- Since Gtk 2.6.
dragSourceAddURITargets :: WidgetClass widget => widget -> IO () Source #
Add the URI targets supported by Selection
to the target list of the
drag source. The targets are added with info = 0
. If you need another
value, use targetListAddTextTargets
and dragSourceSetTargetList
.
- Since Gtk 2.6.
Signals
dragBegin :: WidgetClass self => Signal self (DragContext -> IO ()) Source #
The dragBegin
signal is emitted on the drag source when a drag is
started. A typical reason to connect to this signal is to set up a custom
drag icon with dragSourceSetIcon
.
dragDataDelete :: WidgetClass self => Signal self (DragContext -> IO ()) Source #
The dragDataDelete
signal is emitted on the drag source when a drag
with the action ActionMove
is successfully completed. The signal handler
is responsible for deleting the data that has been dropped. What "delete"
means, depends on the context of the drag operation.
dragDataGet :: WidgetClass self => Signal self (DragContext -> InfoId -> TimeStamp -> SelectionDataM ()) Source #
The dragDataGet
signal is emitted on the drag source when the
drop site requests the data which is dragged. It is the
responsibility of the signal handler to set the selection data in
the format which is indicated by InfoId
. See
selectionDataSet
and
selectionDataSetText
.
dragDataReceived :: WidgetClass self => Signal self (DragContext -> Point -> InfoId -> TimeStamp -> SelectionDataM ()) Source #
The dragDataReceived
signal is emitted on the drop site when the
dragged data has been received. If the data was received in order to
determine whether the drop will be accepted, the handler is expected to call
dragStatus
and not finish the drag. If the data was received in response
to a dragDrop
signal (and this is the last target to be received), the
handler for this signal is expected to process the received data and then
call dragFinish
, setting the success
parameter depending on whether the
data was processed successfully.
The handler may inspect and modify dragContextAction
before calling
dragFinish
, e.g. to implement ActionAsk
as shown in the following
example:
dragDrop :: WidgetClass self => Signal self (DragContext -> Point -> TimeStamp -> IO Bool) Source #
The dragDrop
signal is emitted on the drop site when the user drops
the data onto the widget. The signal handler must determine whether the
cursor position is in a drop zone or not. If it is not in a drop zone, it
returns False
and no further processing is necessary. Otherwise, the
handler returns True
. In this case, the handler must ensure that
dragFinish
is called to let the source know that the drop is done. The
call to dragFinish
can be done either directly or in a
dragDataReceived
handler which gets triggered by calling dropGetData
to receive the data for one or more of the supported targets.
dragEnd :: WidgetClass self => Signal self (DragContext -> IO ()) Source #
dragFailed :: WidgetClass self => Signal self (DragContext -> DragResult -> IO Bool) Source #
The dragFailed
signal is emitted on the drag source when a drag has
failed. The signal handler may hook custom code to handle a failed DND
operation based on the type of error, it returns True
is the failure has
been already handled (not showing the default "drag operation failed"
animation), otherwise it returns False
.
- Available since Gtk+ 2.12.0.
dragLeave :: WidgetClass self => Signal self (DragContext -> TimeStamp -> IO ()) Source #
The dragLeave
signal is emitted on the drop site when the cursor
leaves the widget. A typical reason to connect to this signal is to undo
things done in dragMotion
, e.g. undo highlighting with dragUnhighlight
dragMotion :: WidgetClass self => Signal self (DragContext -> Point -> TimeStamp -> IO Bool) Source #
The dragMotion
signal is emitted on the drop site when the user moves
the cursor over the widget during a drag. The signal handler must determine
whether the cursor position is in a drop zone or not. If it is not in a drop
zone, it returns False
and no further processing is necessary. Otherwise,
the handler returns True
. In this case, the handler is responsible for
providing the necessary information for displaying feedback to the user, by
calling dragStatus
. If the decision whether the drop will be accepted or
rejected can't be made based solely on the cursor position and the type of
the data, the handler may inspect the dragged data by calling dragGetData
and defer the dragStatus
call to the dragDataReceived
handler.
Note that there is no dragEnter
signal. The drag receiver has to keep
track of whether he has received any dragMotion
signals since the last
dragLeave
and if not, treat the dragMotion
signal as an "enter"
signal. Upon an "enter", the handler will typically highlight the drop
site with dragHighlight
.