{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gtk.Objects.Clipboard.Clipboard' object represents a clipboard of data shared
-- between different processes or between different widgets in
-- the same process. Each clipboard is identified by a name encoded as a
-- t'GI.Gdk.Structs.Atom.Atom'. (Conversion to and from strings can be done with
-- 'GI.Gdk.Functions.atomIntern' and 'GI.Gdk.Structs.Atom.atomName'.) The default clipboard
-- corresponds to the “CLIPBOARD” atom; another commonly used clipboard
-- is the “PRIMARY” clipboard, which, in X, traditionally contains
-- the currently selected text.
-- 
-- To support having a number of different formats on the clipboard
-- at the same time, the clipboard mechanism allows providing
-- callbacks instead of the actual data.  When you set the contents
-- of the clipboard, you can either supply the data directly (via
-- functions like 'GI.Gtk.Objects.Clipboard.clipboardSetText'), or you can supply a
-- callback to be called at a later time when the data is needed (via
-- @/gtk_clipboard_set_with_data()/@ or @/gtk_clipboard_set_with_owner()/@.)
-- Providing a callback also avoids having to make copies of the data
-- when it is not needed.
-- 
-- @/gtk_clipboard_set_with_data()/@ and @/gtk_clipboard_set_with_owner()/@
-- are quite similar; the choice between the two depends mostly on
-- which is more convenient in a particular situation.
-- The former is most useful when you want to have a blob of data
-- with callbacks to convert it into the various data types that you
-- advertise. When the /@clearFunc@/ you provided is called, you
-- simply free the data blob. The latter is more useful when the
-- contents of clipboard reflect the internal state of a t'GI.GObject.Objects.Object.Object'
-- (As an example, for the PRIMARY clipboard, when an entry widget
-- provides the clipboard’s contents the contents are simply the
-- text within the selected region.) If the contents change, the
-- entry widget can call @/gtk_clipboard_set_with_owner()/@ to update
-- the timestamp for clipboard ownership, without having to worry
-- about /@clearFunc@/ being called.
-- 
-- Requesting the data from the clipboard is essentially
-- asynchronous. If the contents of the clipboard are provided within
-- the same process, then a direct function call will be made to
-- retrieve the data, but if they are provided by another process,
-- then the data needs to be retrieved from the other process, which
-- may take some time. To avoid blocking the user interface, the call
-- to request the selection, 'GI.Gtk.Objects.Clipboard.clipboardRequestContents' takes a
-- callback that will be called when the contents are received (or
-- when the request fails.) If you don’t want to deal with providing
-- a separate callback, you can also use 'GI.Gtk.Objects.Clipboard.clipboardWaitForContents'.
-- What this does is run the GLib main loop recursively waiting for
-- the contents. This can simplify the code flow, but you still have
-- to be aware that other callbacks in your program can be called
-- while this recursive mainloop is running.
-- 
-- Along with the functions to get the clipboard contents as an
-- arbitrary data chunk, there are also functions to retrieve
-- it as text, 'GI.Gtk.Objects.Clipboard.clipboardRequestText' and
-- 'GI.Gtk.Objects.Clipboard.clipboardWaitForText'. These functions take care of
-- determining which formats are advertised by the clipboard
-- provider, asking for the clipboard in the best available format
-- and converting the results into the UTF-8 encoding. (The standard
-- form for representing strings in GTK+.)

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

module GI.Gtk.Objects.Clipboard
    ( 
#if defined(ENABLE_OVERLOADING)
    ClipboardWaitForRichTextMethodInfo      ,
#endif

-- * Exported types
    Clipboard(..)                           ,
    IsClipboard                             ,
    toClipboard                             ,
    noClipboard                             ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveClipboardMethod                  ,
#endif


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    ClipboardClearMethodInfo                ,
#endif
    clipboardClear                          ,


-- ** get #method:get#

    clipboardGet                            ,


-- ** getDefault #method:getDefault#

    clipboardGetDefault                     ,


-- ** getDisplay #method:getDisplay#

#if defined(ENABLE_OVERLOADING)
    ClipboardGetDisplayMethodInfo           ,
#endif
    clipboardGetDisplay                     ,


-- ** getForDisplay #method:getForDisplay#

    clipboardGetForDisplay                  ,


-- ** getOwner #method:getOwner#

#if defined(ENABLE_OVERLOADING)
    ClipboardGetOwnerMethodInfo             ,
#endif
    clipboardGetOwner                       ,


-- ** requestContents #method:requestContents#

#if defined(ENABLE_OVERLOADING)
    ClipboardRequestContentsMethodInfo      ,
#endif
    clipboardRequestContents                ,


-- ** requestImage #method:requestImage#

#if defined(ENABLE_OVERLOADING)
    ClipboardRequestImageMethodInfo         ,
#endif
    clipboardRequestImage                   ,


-- ** requestRichText #method:requestRichText#

#if defined(ENABLE_OVERLOADING)
    ClipboardRequestRichTextMethodInfo      ,
#endif
    clipboardRequestRichText                ,


-- ** requestTargets #method:requestTargets#

#if defined(ENABLE_OVERLOADING)
    ClipboardRequestTargetsMethodInfo       ,
#endif
    clipboardRequestTargets                 ,


-- ** requestText #method:requestText#

#if defined(ENABLE_OVERLOADING)
    ClipboardRequestTextMethodInfo          ,
#endif
    clipboardRequestText                    ,


-- ** requestUris #method:requestUris#

#if defined(ENABLE_OVERLOADING)
    ClipboardRequestUrisMethodInfo          ,
#endif
    clipboardRequestUris                    ,


-- ** setCanStore #method:setCanStore#

#if defined(ENABLE_OVERLOADING)
    ClipboardSetCanStoreMethodInfo          ,
#endif
    clipboardSetCanStore                    ,


-- ** setImage #method:setImage#

#if defined(ENABLE_OVERLOADING)
    ClipboardSetImageMethodInfo             ,
#endif
    clipboardSetImage                       ,


-- ** setText #method:setText#

#if defined(ENABLE_OVERLOADING)
    ClipboardSetTextMethodInfo              ,
#endif
    clipboardSetText                        ,


-- ** store #method:store#

#if defined(ENABLE_OVERLOADING)
    ClipboardStoreMethodInfo                ,
#endif
    clipboardStore                          ,


-- ** waitForContents #method:waitForContents#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitForContentsMethodInfo      ,
#endif
    clipboardWaitForContents                ,


-- ** waitForImage #method:waitForImage#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitForImageMethodInfo         ,
#endif
    clipboardWaitForImage                   ,


-- ** waitForTargets #method:waitForTargets#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitForTargetsMethodInfo       ,
#endif
    clipboardWaitForTargets                 ,


-- ** waitForText #method:waitForText#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitForTextMethodInfo          ,
#endif
    clipboardWaitForText                    ,


-- ** waitForUris #method:waitForUris#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitForUrisMethodInfo          ,
#endif
    clipboardWaitForUris                    ,


-- ** waitIsImageAvailable #method:waitIsImageAvailable#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitIsImageAvailableMethodInfo ,
#endif
    clipboardWaitIsImageAvailable           ,


-- ** waitIsRichTextAvailable #method:waitIsRichTextAvailable#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitIsRichTextAvailableMethodInfo,
#endif
    clipboardWaitIsRichTextAvailable        ,


-- ** waitIsTargetAvailable #method:waitIsTargetAvailable#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitIsTargetAvailableMethodInfo,
#endif
    clipboardWaitIsTargetAvailable          ,


-- ** waitIsTextAvailable #method:waitIsTextAvailable#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitIsTextAvailableMethodInfo  ,
#endif
    clipboardWaitIsTextAvailable            ,


-- ** waitIsUrisAvailable #method:waitIsUrisAvailable#

#if defined(ENABLE_OVERLOADING)
    ClipboardWaitIsUrisAvailableMethodInfo  ,
#endif
    clipboardWaitIsUrisAvailable            ,




 -- * Signals
-- ** ownerChange #signal:ownerChange#

    C_ClipboardOwnerChangeCallback          ,
    ClipboardOwnerChangeCallback            ,
#if defined(ENABLE_OVERLOADING)
    ClipboardOwnerChangeSignalInfo          ,
#endif
    afterClipboardOwnerChange               ,
    genClosure_ClipboardOwnerChange         ,
    mk_ClipboardOwnerChangeCallback         ,
    noClipboardOwnerChangeCallback          ,
    onClipboardOwnerChange                  ,
    wrap_ClipboardOwnerChangeCallback       ,




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
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 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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Structs.Atom as Gdk.Atom
import qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextBuffer as Gtk.TextBuffer
import {-# SOURCE #-} qualified GI.Gtk.Structs.SelectionData as Gtk.SelectionData
import {-# SOURCE #-} qualified GI.Gtk.Structs.TargetEntry as Gtk.TargetEntry

-- | Memory-managed wrapper type.
newtype Clipboard = Clipboard (ManagedPtr Clipboard)
    deriving (Clipboard -> Clipboard -> Bool
(Clipboard -> Clipboard -> Bool)
-> (Clipboard -> Clipboard -> Bool) -> Eq Clipboard
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Clipboard -> Clipboard -> Bool
$c/= :: Clipboard -> Clipboard -> Bool
== :: Clipboard -> Clipboard -> Bool
$c== :: Clipboard -> Clipboard -> Bool
Eq)
foreign import ccall "gtk_clipboard_get_type"
    c_gtk_clipboard_get_type :: IO GType

instance GObject Clipboard where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_clipboard_get_type
    

-- | Convert 'Clipboard' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Clipboard where
    toGValue :: Clipboard -> IO GValue
toGValue o :: Clipboard
o = do
        GType
gtype <- IO GType
c_gtk_clipboard_get_type
        Clipboard -> (Ptr Clipboard -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Clipboard
o (GType
-> (GValue -> Ptr Clipboard -> IO ()) -> Ptr Clipboard -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Clipboard -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Clipboard
fromGValue gv :: GValue
gv = do
        Ptr Clipboard
ptr <- GValue -> IO (Ptr Clipboard)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Clipboard)
        (ManagedPtr Clipboard -> Clipboard)
-> Ptr Clipboard -> IO Clipboard
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Clipboard -> Clipboard
Clipboard Ptr Clipboard
ptr
        
    

-- | Type class for types which can be safely cast to `Clipboard`, for instance with `toClipboard`.
class (GObject o, O.IsDescendantOf Clipboard o) => IsClipboard o
instance (GObject o, O.IsDescendantOf Clipboard o) => IsClipboard o

instance O.HasParentTypes Clipboard
type instance O.ParentTypes Clipboard = '[GObject.Object.Object]

-- | Cast to `Clipboard`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toClipboard :: (MonadIO m, IsClipboard o) => o -> m Clipboard
toClipboard :: o -> m Clipboard
toClipboard = IO Clipboard -> m Clipboard
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Clipboard -> m Clipboard)
-> (o -> IO Clipboard) -> o -> m Clipboard
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Clipboard -> Clipboard) -> o -> IO Clipboard
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Clipboard -> Clipboard
Clipboard

-- | A convenience alias for `Nothing` :: `Maybe` `Clipboard`.
noClipboard :: Maybe Clipboard
noClipboard :: Maybe Clipboard
noClipboard = Maybe Clipboard
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveClipboardMethod (t :: Symbol) (o :: *) :: * where
    ResolveClipboardMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveClipboardMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveClipboardMethod "clear" o = ClipboardClearMethodInfo
    ResolveClipboardMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveClipboardMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveClipboardMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveClipboardMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveClipboardMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveClipboardMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveClipboardMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveClipboardMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveClipboardMethod "requestContents" o = ClipboardRequestContentsMethodInfo
    ResolveClipboardMethod "requestImage" o = ClipboardRequestImageMethodInfo
    ResolveClipboardMethod "requestRichText" o = ClipboardRequestRichTextMethodInfo
    ResolveClipboardMethod "requestTargets" o = ClipboardRequestTargetsMethodInfo
    ResolveClipboardMethod "requestText" o = ClipboardRequestTextMethodInfo
    ResolveClipboardMethod "requestUris" o = ClipboardRequestUrisMethodInfo
    ResolveClipboardMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveClipboardMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveClipboardMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveClipboardMethod "store" o = ClipboardStoreMethodInfo
    ResolveClipboardMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveClipboardMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveClipboardMethod "waitForContents" o = ClipboardWaitForContentsMethodInfo
    ResolveClipboardMethod "waitForImage" o = ClipboardWaitForImageMethodInfo
    ResolveClipboardMethod "waitForRichText" o = ClipboardWaitForRichTextMethodInfo
    ResolveClipboardMethod "waitForTargets" o = ClipboardWaitForTargetsMethodInfo
    ResolveClipboardMethod "waitForText" o = ClipboardWaitForTextMethodInfo
    ResolveClipboardMethod "waitForUris" o = ClipboardWaitForUrisMethodInfo
    ResolveClipboardMethod "waitIsImageAvailable" o = ClipboardWaitIsImageAvailableMethodInfo
    ResolveClipboardMethod "waitIsRichTextAvailable" o = ClipboardWaitIsRichTextAvailableMethodInfo
    ResolveClipboardMethod "waitIsTargetAvailable" o = ClipboardWaitIsTargetAvailableMethodInfo
    ResolveClipboardMethod "waitIsTextAvailable" o = ClipboardWaitIsTextAvailableMethodInfo
    ResolveClipboardMethod "waitIsUrisAvailable" o = ClipboardWaitIsUrisAvailableMethodInfo
    ResolveClipboardMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveClipboardMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveClipboardMethod "getDisplay" o = ClipboardGetDisplayMethodInfo
    ResolveClipboardMethod "getOwner" o = ClipboardGetOwnerMethodInfo
    ResolveClipboardMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveClipboardMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveClipboardMethod "setCanStore" o = ClipboardSetCanStoreMethodInfo
    ResolveClipboardMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveClipboardMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveClipboardMethod "setImage" o = ClipboardSetImageMethodInfo
    ResolveClipboardMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveClipboardMethod "setText" o = ClipboardSetTextMethodInfo
    ResolveClipboardMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveClipboardMethod t Clipboard, O.MethodInfo info Clipboard p) => OL.IsLabel t (Clipboard -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal Clipboard::owner-change
-- | The [ownerChange](#signal:ownerChange) signal is emitted when GTK+ receives an
-- event that indicates that the ownership of the selection
-- associated with /@clipboard@/ has changed.
-- 
-- /Since: 2.6/
type ClipboardOwnerChangeCallback =
    Gdk.EventOwnerChange.EventOwnerChange
    -- ^ /@event@/: the /@gdkEventOwnerChange@/ event
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ClipboardOwnerChangeCallback`@.
noClipboardOwnerChangeCallback :: Maybe ClipboardOwnerChangeCallback
noClipboardOwnerChangeCallback :: Maybe ClipboardOwnerChangeCallback
noClipboardOwnerChangeCallback = Maybe ClipboardOwnerChangeCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ClipboardOwnerChangeCallback =
    Ptr () ->                               -- object
    Ptr Gdk.EventOwnerChange.EventOwnerChange ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_ClipboardOwnerChange :: MonadIO m => ClipboardOwnerChangeCallback -> m (GClosure C_ClipboardOwnerChangeCallback)
genClosure_ClipboardOwnerChange :: ClipboardOwnerChangeCallback
-> m (GClosure C_ClipboardOwnerChangeCallback)
genClosure_ClipboardOwnerChange cb :: ClipboardOwnerChangeCallback
cb = IO (GClosure C_ClipboardOwnerChangeCallback)
-> m (GClosure C_ClipboardOwnerChangeCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ClipboardOwnerChangeCallback)
 -> m (GClosure C_ClipboardOwnerChangeCallback))
-> IO (GClosure C_ClipboardOwnerChangeCallback)
-> m (GClosure C_ClipboardOwnerChangeCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ClipboardOwnerChangeCallback
cb' = ClipboardOwnerChangeCallback -> C_ClipboardOwnerChangeCallback
wrap_ClipboardOwnerChangeCallback ClipboardOwnerChangeCallback
cb
    C_ClipboardOwnerChangeCallback
-> IO (FunPtr C_ClipboardOwnerChangeCallback)
mk_ClipboardOwnerChangeCallback C_ClipboardOwnerChangeCallback
cb' IO (FunPtr C_ClipboardOwnerChangeCallback)
-> (FunPtr C_ClipboardOwnerChangeCallback
    -> IO (GClosure C_ClipboardOwnerChangeCallback))
-> IO (GClosure C_ClipboardOwnerChangeCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ClipboardOwnerChangeCallback
-> IO (GClosure C_ClipboardOwnerChangeCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ClipboardOwnerChangeCallback` into a `C_ClipboardOwnerChangeCallback`.
wrap_ClipboardOwnerChangeCallback ::
    ClipboardOwnerChangeCallback ->
    C_ClipboardOwnerChangeCallback
wrap_ClipboardOwnerChangeCallback :: ClipboardOwnerChangeCallback -> C_ClipboardOwnerChangeCallback
wrap_ClipboardOwnerChangeCallback _cb :: ClipboardOwnerChangeCallback
_cb _ event :: Ptr EventOwnerChange
event _ = do
    EventOwnerChange
event' <- ((ManagedPtr EventOwnerChange -> EventOwnerChange)
-> Ptr EventOwnerChange -> IO EventOwnerChange
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr EventOwnerChange -> EventOwnerChange
Gdk.EventOwnerChange.EventOwnerChange) Ptr EventOwnerChange
event
    ClipboardOwnerChangeCallback
_cb  EventOwnerChange
event'


-- | Connect a signal handler for the [ownerChange](#signal:ownerChange) 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' clipboard #ownerChange callback
-- @
-- 
-- 
onClipboardOwnerChange :: (IsClipboard a, MonadIO m) => a -> ClipboardOwnerChangeCallback -> m SignalHandlerId
onClipboardOwnerChange :: a -> ClipboardOwnerChangeCallback -> m SignalHandlerId
onClipboardOwnerChange obj :: a
obj cb :: ClipboardOwnerChangeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_ClipboardOwnerChangeCallback
cb' = ClipboardOwnerChangeCallback -> C_ClipboardOwnerChangeCallback
wrap_ClipboardOwnerChangeCallback ClipboardOwnerChangeCallback
cb
    FunPtr C_ClipboardOwnerChangeCallback
cb'' <- C_ClipboardOwnerChangeCallback
-> IO (FunPtr C_ClipboardOwnerChangeCallback)
mk_ClipboardOwnerChangeCallback C_ClipboardOwnerChangeCallback
cb'
    a
-> Text
-> FunPtr C_ClipboardOwnerChangeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "owner-change" FunPtr C_ClipboardOwnerChangeCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [ownerChange](#signal:ownerChange) 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' clipboard #ownerChange callback
-- @
-- 
-- 
afterClipboardOwnerChange :: (IsClipboard a, MonadIO m) => a -> ClipboardOwnerChangeCallback -> m SignalHandlerId
afterClipboardOwnerChange :: a -> ClipboardOwnerChangeCallback -> m SignalHandlerId
afterClipboardOwnerChange obj :: a
obj cb :: ClipboardOwnerChangeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_ClipboardOwnerChangeCallback
cb' = ClipboardOwnerChangeCallback -> C_ClipboardOwnerChangeCallback
wrap_ClipboardOwnerChangeCallback ClipboardOwnerChangeCallback
cb
    FunPtr C_ClipboardOwnerChangeCallback
cb'' <- C_ClipboardOwnerChangeCallback
-> IO (FunPtr C_ClipboardOwnerChangeCallback)
mk_ClipboardOwnerChangeCallback C_ClipboardOwnerChangeCallback
cb'
    a
-> Text
-> FunPtr C_ClipboardOwnerChangeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "owner-change" FunPtr C_ClipboardOwnerChangeCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data ClipboardOwnerChangeSignalInfo
instance SignalInfo ClipboardOwnerChangeSignalInfo where
    type HaskellCallbackType ClipboardOwnerChangeSignalInfo = ClipboardOwnerChangeCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ClipboardOwnerChangeCallback cb
        cb'' <- mk_ClipboardOwnerChangeCallback cb'
        connectSignalFunPtr obj "owner-change" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Clipboard
type instance O.AttributeList Clipboard = ClipboardAttributeList
type ClipboardAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Clipboard = ClipboardSignalList
type ClipboardSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("ownerChange", ClipboardOwnerChangeSignalInfo)] :: [(Symbol, *)])

#endif

-- method Clipboard::clear
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_clear" gtk_clipboard_clear :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO ()

-- | Clears the contents of the clipboard. Generally this should only
-- be called between the time you call @/gtk_clipboard_set_with_owner()/@
-- or @/gtk_clipboard_set_with_data()/@,
-- and when the /@clearFunc@/ you supplied is called. Otherwise, the
-- clipboard may be owned by someone else.
clipboardClear ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m ()
clipboardClear :: a -> m ()
clipboardClear clipboard :: a
clipboard = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Clipboard -> IO ()
gtk_clipboard_clear Ptr Clipboard
clipboard'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardClearMethodInfo
instance (signature ~ (m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardClearMethodInfo a signature where
    overloadedMethod = clipboardClear

#endif

-- method Clipboard::get_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Display" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_get_display" gtk_clipboard_get_display :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO (Ptr Gdk.Display.Display)

-- | Gets the t'GI.Gdk.Objects.Display.Display' associated with /@clipboard@/
-- 
-- /Since: 2.2/
clipboardGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m Gdk.Display.Display
    -- ^ __Returns:__ the t'GI.Gdk.Objects.Display.Display' associated with /@clipboard@/
clipboardGetDisplay :: a -> m Display
clipboardGetDisplay clipboard :: a
clipboard = IO Display -> m Display
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Display -> m Display) -> IO Display -> m Display
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Display
result <- Ptr Clipboard -> IO (Ptr Display)
gtk_clipboard_get_display Ptr Clipboard
clipboard'
    Text -> Ptr Display -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "clipboardGetDisplay" Ptr Display
result
    Display
result' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Display -> IO Display
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result'

#if defined(ENABLE_OVERLOADING)
data ClipboardGetDisplayMethodInfo
instance (signature ~ (m Gdk.Display.Display), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardGetDisplayMethodInfo a signature where
    overloadedMethod = clipboardGetDisplay

#endif

-- method Clipboard::get_owner
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GObject" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_get_owner" gtk_clipboard_get_owner :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO (Ptr GObject.Object.Object)

-- | If the clipboard contents callbacks were set with
-- @/gtk_clipboard_set_with_owner()/@, and the @/gtk_clipboard_set_with_data()/@ or
-- 'GI.Gtk.Objects.Clipboard.clipboardClear' has not subsequently called, returns the owner set
-- by @/gtk_clipboard_set_with_owner()/@.
clipboardGetOwner ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m (Maybe GObject.Object.Object)
    -- ^ __Returns:__ the owner of the clipboard, if any;
    --     otherwise 'P.Nothing'.
clipboardGetOwner :: a -> m (Maybe Object)
clipboardGetOwner clipboard :: a
clipboard = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Object
result <- Ptr Clipboard -> IO (Ptr Object)
gtk_clipboard_get_owner Ptr Clipboard
clipboard'
    Maybe Object
maybeResult <- Ptr Object -> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Object
result ((Ptr Object -> IO Object) -> IO (Maybe Object))
-> (Ptr Object -> IO Object) -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Object
result' -> do
        Object
result'' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
GObject.Object.Object) Ptr Object
result'
        Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
maybeResult

#if defined(ENABLE_OVERLOADING)
data ClipboardGetOwnerMethodInfo
instance (signature ~ (m (Maybe GObject.Object.Object)), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardGetOwnerMethodInfo a signature where
    overloadedMethod = clipboardGetOwner

#endif

-- method Clipboard::request_contents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Atom" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an atom representing the form into which the clipboard\n    owner should convert the selection."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ClipboardReceivedFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A function to call when the results are received\n    (or the retrieval fails). If the retrieval fails the length field of\n    @selection_data will be negative."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_request_contents" gtk_clipboard_request_contents :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    Ptr Gdk.Atom.Atom ->                    -- target : TInterface (Name {namespace = "Gdk", name = "Atom"})
    FunPtr Gtk.Callbacks.C_ClipboardReceivedFunc -> -- callback : TInterface (Name {namespace = "Gtk", name = "ClipboardReceivedFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Requests the contents of clipboard as the given target.
-- When the results of the result are later received the supplied callback
-- will be called.
clipboardRequestContents ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> Gdk.Atom.Atom
    -- ^ /@target@/: an atom representing the form into which the clipboard
    --     owner should convert the selection.
    -> Gtk.Callbacks.ClipboardReceivedFunc
    -- ^ /@callback@/: A function to call when the results are received
    --     (or the retrieval fails). If the retrieval fails the length field of
    --     /@selectionData@/ will be negative.
    -> m ()
clipboardRequestContents :: a -> Atom -> ClipboardReceivedFunc -> m ()
clipboardRequestContents clipboard :: a
clipboard target :: Atom
target callback :: ClipboardReceivedFunc
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Atom
target' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
target
    Ptr (FunPtr C_ClipboardReceivedFunc)
ptrcallback <- IO (Ptr (FunPtr C_ClipboardReceivedFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gtk.Callbacks.C_ClipboardReceivedFunc))
    FunPtr C_ClipboardReceivedFunc
callback' <- C_ClipboardReceivedFunc -> IO (FunPtr C_ClipboardReceivedFunc)
Gtk.Callbacks.mk_ClipboardReceivedFunc (Maybe (Ptr (FunPtr C_ClipboardReceivedFunc))
-> ClipboardReceivedFunc_WithClosures -> C_ClipboardReceivedFunc
Gtk.Callbacks.wrap_ClipboardReceivedFunc (Ptr (FunPtr C_ClipboardReceivedFunc)
-> Maybe (Ptr (FunPtr C_ClipboardReceivedFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_ClipboardReceivedFunc)
ptrcallback) (ClipboardReceivedFunc -> ClipboardReceivedFunc_WithClosures
Gtk.Callbacks.drop_closures_ClipboardReceivedFunc ClipboardReceivedFunc
callback))
    Ptr (FunPtr C_ClipboardReceivedFunc)
-> FunPtr C_ClipboardReceivedFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_ClipboardReceivedFunc)
ptrcallback FunPtr C_ClipboardReceivedFunc
callback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Clipboard
-> Ptr Atom -> FunPtr C_ClipboardReceivedFunc -> Ptr () -> IO ()
gtk_clipboard_request_contents Ptr Clipboard
clipboard' Ptr Atom
target' FunPtr C_ClipboardReceivedFunc
callback' Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
target
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardRequestContentsMethodInfo
instance (signature ~ (Gdk.Atom.Atom -> Gtk.Callbacks.ClipboardReceivedFunc -> m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardRequestContentsMethodInfo a signature where
    overloadedMethod = clipboardRequestContents

#endif

-- method Clipboard::request_image
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ClipboardImageReceivedFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function to call when the image is received,\n    or the retrieval fails. (It will always be called one way or the other.)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_request_image" gtk_clipboard_request_image :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    FunPtr Gtk.Callbacks.C_ClipboardImageReceivedFunc -> -- callback : TInterface (Name {namespace = "Gtk", name = "ClipboardImageReceivedFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Requests the contents of the clipboard as image. When the image is
-- later received, it will be converted to a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf', and
-- /@callback@/ will be called.
-- 
-- The /@pixbuf@/ parameter to /@callback@/ will contain the resulting
-- t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf' if the request succeeded, or 'P.Nothing' if it failed. This
-- could happen for various reasons, in particular if the clipboard
-- was empty or if the contents of the clipboard could not be
-- converted into an image.
-- 
-- /Since: 2.6/
clipboardRequestImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> Gtk.Callbacks.ClipboardImageReceivedFunc
    -- ^ /@callback@/: a function to call when the image is received,
    --     or the retrieval fails. (It will always be called one way or the other.)
    -> m ()
clipboardRequestImage :: a -> ClipboardImageReceivedFunc -> m ()
clipboardRequestImage clipboard :: a
clipboard callback :: ClipboardImageReceivedFunc
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr (FunPtr C_ClipboardImageReceivedFunc)
ptrcallback <- IO (Ptr (FunPtr C_ClipboardImageReceivedFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gtk.Callbacks.C_ClipboardImageReceivedFunc))
    FunPtr C_ClipboardImageReceivedFunc
callback' <- C_ClipboardImageReceivedFunc
-> IO (FunPtr C_ClipboardImageReceivedFunc)
Gtk.Callbacks.mk_ClipboardImageReceivedFunc (Maybe (Ptr (FunPtr C_ClipboardImageReceivedFunc))
-> ClipboardImageReceivedFunc_WithClosures
-> C_ClipboardImageReceivedFunc
Gtk.Callbacks.wrap_ClipboardImageReceivedFunc (Ptr (FunPtr C_ClipboardImageReceivedFunc)
-> Maybe (Ptr (FunPtr C_ClipboardImageReceivedFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_ClipboardImageReceivedFunc)
ptrcallback) (ClipboardImageReceivedFunc
-> ClipboardImageReceivedFunc_WithClosures
Gtk.Callbacks.drop_closures_ClipboardImageReceivedFunc ClipboardImageReceivedFunc
callback))
    Ptr (FunPtr C_ClipboardImageReceivedFunc)
-> FunPtr C_ClipboardImageReceivedFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_ClipboardImageReceivedFunc)
ptrcallback FunPtr C_ClipboardImageReceivedFunc
callback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Clipboard
-> FunPtr C_ClipboardImageReceivedFunc -> Ptr () -> IO ()
gtk_clipboard_request_image Ptr Clipboard
clipboard' FunPtr C_ClipboardImageReceivedFunc
callback' Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardRequestImageMethodInfo
instance (signature ~ (Gtk.Callbacks.ClipboardImageReceivedFunc -> m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardRequestImageMethodInfo a signature where
    overloadedMethod = clipboardRequestImage

#endif

-- method Clipboard::request_rich_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextBuffer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextBuffer" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ClipboardRichTextReceivedFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function to call when the text is received,\n    or the retrieval fails. (It will always be called one way or the other.)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_request_rich_text" gtk_clipboard_request_rich_text :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    Ptr Gtk.TextBuffer.TextBuffer ->        -- buffer : TInterface (Name {namespace = "Gtk", name = "TextBuffer"})
    FunPtr Gtk.Callbacks.C_ClipboardRichTextReceivedFunc -> -- callback : TInterface (Name {namespace = "Gtk", name = "ClipboardRichTextReceivedFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Requests the contents of the clipboard as rich text. When the rich
-- text is later received, /@callback@/ will be called.
-- 
-- The /@text@/ parameter to /@callback@/ will contain the resulting rich
-- text if the request succeeded, or 'P.Nothing' if it failed. The /@length@/
-- parameter will contain /@text@/’s length. This function can fail for
-- various reasons, in particular if the clipboard was empty or if the
-- contents of the clipboard could not be converted into rich text form.
-- 
-- /Since: 2.10/
clipboardRequestRichText ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a, Gtk.TextBuffer.IsTextBuffer b) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> b
    -- ^ /@buffer@/: a t'GI.Gtk.Objects.TextBuffer.TextBuffer'
    -> Gtk.Callbacks.ClipboardRichTextReceivedFunc
    -- ^ /@callback@/: a function to call when the text is received,
    --     or the retrieval fails. (It will always be called one way or the other.)
    -> m ()
clipboardRequestRichText :: a -> b -> ClipboardRichTextReceivedFunc -> m ()
clipboardRequestRichText clipboard :: a
clipboard buffer :: b
buffer callback :: ClipboardRichTextReceivedFunc
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr TextBuffer
buffer' <- b -> IO (Ptr TextBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
buffer
    Ptr (FunPtr C_ClipboardRichTextReceivedFunc)
ptrcallback <- IO (Ptr (FunPtr C_ClipboardRichTextReceivedFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gtk.Callbacks.C_ClipboardRichTextReceivedFunc))
    FunPtr C_ClipboardRichTextReceivedFunc
callback' <- C_ClipboardRichTextReceivedFunc
-> IO (FunPtr C_ClipboardRichTextReceivedFunc)
Gtk.Callbacks.mk_ClipboardRichTextReceivedFunc (Maybe (Ptr (FunPtr C_ClipboardRichTextReceivedFunc))
-> ClipboardRichTextReceivedFunc_WithClosures
-> C_ClipboardRichTextReceivedFunc
Gtk.Callbacks.wrap_ClipboardRichTextReceivedFunc (Ptr (FunPtr C_ClipboardRichTextReceivedFunc)
-> Maybe (Ptr (FunPtr C_ClipboardRichTextReceivedFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_ClipboardRichTextReceivedFunc)
ptrcallback) (ClipboardRichTextReceivedFunc
-> ClipboardRichTextReceivedFunc_WithClosures
Gtk.Callbacks.drop_closures_ClipboardRichTextReceivedFunc ClipboardRichTextReceivedFunc
callback))
    Ptr (FunPtr C_ClipboardRichTextReceivedFunc)
-> FunPtr C_ClipboardRichTextReceivedFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_ClipboardRichTextReceivedFunc)
ptrcallback FunPtr C_ClipboardRichTextReceivedFunc
callback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Clipboard
-> Ptr TextBuffer
-> FunPtr C_ClipboardRichTextReceivedFunc
-> Ptr ()
-> IO ()
gtk_clipboard_request_rich_text Ptr Clipboard
clipboard' Ptr TextBuffer
buffer' FunPtr C_ClipboardRichTextReceivedFunc
callback' Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
buffer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardRequestRichTextMethodInfo
instance (signature ~ (b -> Gtk.Callbacks.ClipboardRichTextReceivedFunc -> m ()), MonadIO m, IsClipboard a, Gtk.TextBuffer.IsTextBuffer b) => O.MethodInfo ClipboardRequestRichTextMethodInfo a signature where
    overloadedMethod = clipboardRequestRichText

#endif

-- method Clipboard::request_targets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ClipboardTargetsReceivedFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function to call when the targets are\n    received, or the retrieval fails. (It will always be called\n    one way or the other.)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_request_targets" gtk_clipboard_request_targets :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    FunPtr Gtk.Callbacks.C_ClipboardTargetsReceivedFunc -> -- callback : TInterface (Name {namespace = "Gtk", name = "ClipboardTargetsReceivedFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Requests the contents of the clipboard as list of supported targets.
-- When the list is later received, /@callback@/ will be called.
-- 
-- The /@targets@/ parameter to /@callback@/ will contain the resulting targets if
-- the request succeeded, or 'P.Nothing' if it failed.
-- 
-- /Since: 2.4/
clipboardRequestTargets ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> Gtk.Callbacks.ClipboardTargetsReceivedFunc
    -- ^ /@callback@/: a function to call when the targets are
    --     received, or the retrieval fails. (It will always be called
    --     one way or the other.)
    -> m ()
clipboardRequestTargets :: a -> ClipboardTargetsReceivedFunc -> m ()
clipboardRequestTargets clipboard :: a
clipboard callback :: ClipboardTargetsReceivedFunc
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr (FunPtr C_ClipboardTargetsReceivedFunc)
ptrcallback <- IO (Ptr (FunPtr C_ClipboardTargetsReceivedFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gtk.Callbacks.C_ClipboardTargetsReceivedFunc))
    FunPtr C_ClipboardTargetsReceivedFunc
callback' <- C_ClipboardTargetsReceivedFunc
-> IO (FunPtr C_ClipboardTargetsReceivedFunc)
Gtk.Callbacks.mk_ClipboardTargetsReceivedFunc (Maybe (Ptr (FunPtr C_ClipboardTargetsReceivedFunc))
-> ClipboardTargetsReceivedFunc_WithClosures
-> C_ClipboardTargetsReceivedFunc
Gtk.Callbacks.wrap_ClipboardTargetsReceivedFunc (Ptr (FunPtr C_ClipboardTargetsReceivedFunc)
-> Maybe (Ptr (FunPtr C_ClipboardTargetsReceivedFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_ClipboardTargetsReceivedFunc)
ptrcallback) (ClipboardTargetsReceivedFunc
-> ClipboardTargetsReceivedFunc_WithClosures
Gtk.Callbacks.drop_closures_ClipboardTargetsReceivedFunc ClipboardTargetsReceivedFunc
callback))
    Ptr (FunPtr C_ClipboardTargetsReceivedFunc)
-> FunPtr C_ClipboardTargetsReceivedFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_ClipboardTargetsReceivedFunc)
ptrcallback FunPtr C_ClipboardTargetsReceivedFunc
callback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Clipboard
-> FunPtr C_ClipboardTargetsReceivedFunc -> Ptr () -> IO ()
gtk_clipboard_request_targets Ptr Clipboard
clipboard' FunPtr C_ClipboardTargetsReceivedFunc
callback' Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardRequestTargetsMethodInfo
instance (signature ~ (Gtk.Callbacks.ClipboardTargetsReceivedFunc -> m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardRequestTargetsMethodInfo a signature where
    overloadedMethod = clipboardRequestTargets

#endif

-- method Clipboard::request_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ClipboardTextReceivedFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function to call when the text is received,\n    or the retrieval fails. (It will always be called one way or the other.)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_request_text" gtk_clipboard_request_text :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    FunPtr Gtk.Callbacks.C_ClipboardTextReceivedFunc -> -- callback : TInterface (Name {namespace = "Gtk", name = "ClipboardTextReceivedFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Requests the contents of the clipboard as text. When the text is
-- later received, it will be converted to UTF-8 if necessary, and
-- /@callback@/ will be called.
-- 
-- The /@text@/ parameter to /@callback@/ will contain the resulting text if
-- the request succeeded, or 'P.Nothing' if it failed. This could happen for
-- various reasons, in particular if the clipboard was empty or if the
-- contents of the clipboard could not be converted into text form.
clipboardRequestText ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> Gtk.Callbacks.ClipboardTextReceivedFunc
    -- ^ /@callback@/: a function to call when the text is received,
    --     or the retrieval fails. (It will always be called one way or the other.)
    -> m ()
clipboardRequestText :: a -> ClipboardTextReceivedFunc -> m ()
clipboardRequestText clipboard :: a
clipboard callback :: ClipboardTextReceivedFunc
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr (FunPtr C_ClipboardTextReceivedFunc)
ptrcallback <- IO (Ptr (FunPtr C_ClipboardTextReceivedFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gtk.Callbacks.C_ClipboardTextReceivedFunc))
    FunPtr C_ClipboardTextReceivedFunc
callback' <- C_ClipboardTextReceivedFunc
-> IO (FunPtr C_ClipboardTextReceivedFunc)
Gtk.Callbacks.mk_ClipboardTextReceivedFunc (Maybe (Ptr (FunPtr C_ClipboardTextReceivedFunc))
-> ClipboardTextReceivedFunc_WithClosures
-> C_ClipboardTextReceivedFunc
Gtk.Callbacks.wrap_ClipboardTextReceivedFunc (Ptr (FunPtr C_ClipboardTextReceivedFunc)
-> Maybe (Ptr (FunPtr C_ClipboardTextReceivedFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_ClipboardTextReceivedFunc)
ptrcallback) (ClipboardTextReceivedFunc -> ClipboardTextReceivedFunc_WithClosures
Gtk.Callbacks.drop_closures_ClipboardTextReceivedFunc ClipboardTextReceivedFunc
callback))
    Ptr (FunPtr C_ClipboardTextReceivedFunc)
-> FunPtr C_ClipboardTextReceivedFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_ClipboardTextReceivedFunc)
ptrcallback FunPtr C_ClipboardTextReceivedFunc
callback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Clipboard
-> FunPtr C_ClipboardTextReceivedFunc -> Ptr () -> IO ()
gtk_clipboard_request_text Ptr Clipboard
clipboard' FunPtr C_ClipboardTextReceivedFunc
callback' Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardRequestTextMethodInfo
instance (signature ~ (Gtk.Callbacks.ClipboardTextReceivedFunc -> m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardRequestTextMethodInfo a signature where
    overloadedMethod = clipboardRequestText

#endif

-- method Clipboard::request_uris
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ClipboardURIReceivedFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a function to call when the URIs are received,\n    or the retrieval fails. (It will always be called one way or the other.)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data to pass to @callback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_request_uris" gtk_clipboard_request_uris :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    FunPtr Gtk.Callbacks.C_ClipboardURIReceivedFunc -> -- callback : TInterface (Name {namespace = "Gtk", name = "ClipboardURIReceivedFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Requests the contents of the clipboard as URIs. When the URIs are
-- later received /@callback@/ will be called.
-- 
-- The /@uris@/ parameter to /@callback@/ will contain the resulting array of
-- URIs if the request succeeded, or 'P.Nothing' if it failed. This could happen
-- for various reasons, in particular if the clipboard was empty or if the
-- contents of the clipboard could not be converted into URI form.
-- 
-- /Since: 2.14/
clipboardRequestUris ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> Gtk.Callbacks.ClipboardURIReceivedFunc
    -- ^ /@callback@/: a function to call when the URIs are received,
    --     or the retrieval fails. (It will always be called one way or the other.)
    -> m ()
clipboardRequestUris :: a -> ClipboardURIReceivedFunc -> m ()
clipboardRequestUris clipboard :: a
clipboard callback :: ClipboardURIReceivedFunc
callback = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr (FunPtr C_ClipboardURIReceivedFunc)
ptrcallback <- IO (Ptr (FunPtr C_ClipboardURIReceivedFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gtk.Callbacks.C_ClipboardURIReceivedFunc))
    FunPtr C_ClipboardURIReceivedFunc
callback' <- C_ClipboardURIReceivedFunc
-> IO (FunPtr C_ClipboardURIReceivedFunc)
Gtk.Callbacks.mk_ClipboardURIReceivedFunc (Maybe (Ptr (FunPtr C_ClipboardURIReceivedFunc))
-> ClipboardURIReceivedFunc_WithClosures
-> C_ClipboardURIReceivedFunc
Gtk.Callbacks.wrap_ClipboardURIReceivedFunc (Ptr (FunPtr C_ClipboardURIReceivedFunc)
-> Maybe (Ptr (FunPtr C_ClipboardURIReceivedFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_ClipboardURIReceivedFunc)
ptrcallback) (ClipboardURIReceivedFunc -> ClipboardURIReceivedFunc_WithClosures
Gtk.Callbacks.drop_closures_ClipboardURIReceivedFunc ClipboardURIReceivedFunc
callback))
    Ptr (FunPtr C_ClipboardURIReceivedFunc)
-> FunPtr C_ClipboardURIReceivedFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_ClipboardURIReceivedFunc)
ptrcallback FunPtr C_ClipboardURIReceivedFunc
callback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Clipboard
-> FunPtr C_ClipboardURIReceivedFunc -> Ptr () -> IO ()
gtk_clipboard_request_uris Ptr Clipboard
clipboard' FunPtr C_ClipboardURIReceivedFunc
callback' Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardRequestUrisMethodInfo
instance (signature ~ (Gtk.Callbacks.ClipboardURIReceivedFunc -> m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardRequestUrisMethodInfo a signature where
    overloadedMethod = clipboardRequestUris

#endif

-- method Clipboard::set_can_store
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "targets"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gtk" , name = "TargetEntry" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "array containing\n          information about which forms should be stored or %NULL\n          to indicate that all forms should be stored."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_targets"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of elements in @targets"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_targets"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of elements in @targets"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_set_can_store" gtk_clipboard_set_can_store :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    Ptr Gtk.TargetEntry.TargetEntry ->      -- targets : TCArray False (-1) 2 (TInterface (Name {namespace = "Gtk", name = "TargetEntry"}))
    Int32 ->                                -- n_targets : TBasicType TInt
    IO ()

-- | Hints that the clipboard data should be stored somewhere when the
-- application exits or when gtk_clipboard_store () is called.
-- 
-- This value is reset when the clipboard owner changes.
-- Where the clipboard data is stored is platform dependent,
-- see gdk_display_store_clipboard () for more information.
-- 
-- /Since: 2.6/
clipboardSetCanStore ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> Maybe ([Gtk.TargetEntry.TargetEntry])
    -- ^ /@targets@/: array containing
    --           information about which forms should be stored or 'P.Nothing'
    --           to indicate that all forms should be stored.
    -> m ()
clipboardSetCanStore :: a -> Maybe [TargetEntry] -> m ()
clipboardSetCanStore clipboard :: a
clipboard targets :: Maybe [TargetEntry]
targets = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let nTargets :: Int32
nTargets = case Maybe [TargetEntry]
targets of
            Nothing -> 0
            Just jTargets :: [TargetEntry]
jTargets -> Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [TargetEntry] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TargetEntry]
jTargets
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr TargetEntry
maybeTargets <- case Maybe [TargetEntry]
targets of
        Nothing -> Ptr TargetEntry -> IO (Ptr TargetEntry)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TargetEntry
forall a. Ptr a
nullPtr
        Just jTargets :: [TargetEntry]
jTargets -> do
            [Ptr TargetEntry]
jTargets' <- (TargetEntry -> IO (Ptr TargetEntry))
-> [TargetEntry] -> IO [Ptr TargetEntry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM TargetEntry -> IO (Ptr TargetEntry)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [TargetEntry]
jTargets
            Ptr TargetEntry
jTargets'' <- Int -> [Ptr TargetEntry] -> IO (Ptr TargetEntry)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 16 [Ptr TargetEntry]
jTargets'
            Ptr TargetEntry -> IO (Ptr TargetEntry)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TargetEntry
jTargets''
    Ptr Clipboard -> Ptr TargetEntry -> Int32 -> IO ()
gtk_clipboard_set_can_store Ptr Clipboard
clipboard' Ptr TargetEntry
maybeTargets Int32
nTargets
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Maybe [TargetEntry] -> ([TargetEntry] -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe [TargetEntry]
targets ((TargetEntry -> IO ()) -> [TargetEntry] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ TargetEntry -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr)
    Ptr TargetEntry -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr TargetEntry
maybeTargets
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardSetCanStoreMethodInfo
instance (signature ~ (Maybe ([Gtk.TargetEntry.TargetEntry]) -> m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardSetCanStoreMethodInfo a signature where
    overloadedMethod = clipboardSetCanStore

#endif

-- method Clipboard::set_image
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pixbuf"
--           , argType =
--               TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkPixbuf" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_set_image" gtk_clipboard_set_image :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO ()

-- | Sets the contents of the clipboard to the given t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'.
-- GTK+ will take responsibility for responding for requests
-- for the image, and for converting the image into the
-- requested format.
-- 
-- /Since: 2.6/
clipboardSetImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a, GdkPixbuf.Pixbuf.IsPixbuf b) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard' object
    -> b
    -- ^ /@pixbuf@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> m ()
clipboardSetImage :: a -> b -> m ()
clipboardSetImage clipboard :: a
clipboard pixbuf :: b
pixbuf = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Pixbuf
pixbuf' <- b -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
pixbuf
    Ptr Clipboard -> Ptr Pixbuf -> IO ()
gtk_clipboard_set_image Ptr Clipboard
clipboard' Ptr Pixbuf
pixbuf'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
pixbuf
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardSetImageMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsClipboard a, GdkPixbuf.Pixbuf.IsPixbuf b) => O.MethodInfo ClipboardSetImageMethodInfo a signature where
    overloadedMethod = clipboardSetImage

#endif

-- method Clipboard::set_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a UTF-8 string." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "length of @text, in bytes, or -1, in which case\n            the length will be determined with strlen()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_set_text" gtk_clipboard_set_text :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- len : TBasicType TInt
    IO ()

-- | Sets the contents of the clipboard to the given UTF-8 string. GTK+ will
-- make a copy of the text and take responsibility for responding
-- for requests for the text, and for converting the text into
-- the requested format.
clipboardSetText ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard' object
    -> T.Text
    -- ^ /@text@/: a UTF-8 string.
    -> Int32
    -- ^ /@len@/: length of /@text@/, in bytes, or -1, in which case
    --             the length will be determined with @/strlen()/@.
    -> m ()
clipboardSetText :: a -> Text -> Int32 -> m ()
clipboardSetText clipboard :: a
clipboard text :: Text
text len :: Int32
len = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    CString
text' <- Text -> IO CString
textToCString Text
text
    Ptr Clipboard -> CString -> Int32 -> IO ()
gtk_clipboard_set_text Ptr Clipboard
clipboard' CString
text' Int32
len
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardSetTextMethodInfo
instance (signature ~ (T.Text -> Int32 -> m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardSetTextMethodInfo a signature where
    overloadedMethod = clipboardSetText

#endif

-- method Clipboard::store
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_store" gtk_clipboard_store :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO ()

-- | Stores the current clipboard data somewhere so that it will stay
-- around after the application has quit.
-- 
-- /Since: 2.6/
clipboardStore ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m ()
clipboardStore :: a -> m ()
clipboardStore clipboard :: a
clipboard = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Clipboard -> IO ()
gtk_clipboard_store Ptr Clipboard
clipboard'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClipboardStoreMethodInfo
instance (signature ~ (m ()), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardStoreMethodInfo a signature where
    overloadedMethod = clipboardStore

#endif

-- method Clipboard::wait_for_contents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Atom" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an atom representing the form into which the clipboard\n         owner should convert the selection."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "SelectionData" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_for_contents" gtk_clipboard_wait_for_contents :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    Ptr Gdk.Atom.Atom ->                    -- target : TInterface (Name {namespace = "Gdk", name = "Atom"})
    IO (Ptr Gtk.SelectionData.SelectionData)

-- | Requests the contents of the clipboard using the given target.
-- This function waits for the data to be received using the main
-- loop, so events, timeouts, etc, may be dispatched during the wait.
clipboardWaitForContents ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> Gdk.Atom.Atom
    -- ^ /@target@/: an atom representing the form into which the clipboard
    --          owner should convert the selection.
    -> m (Maybe Gtk.SelectionData.SelectionData)
    -- ^ __Returns:__ a newly-allocated t'GI.Gtk.Structs.SelectionData.SelectionData' object or 'P.Nothing'
    --               if retrieving the given target failed. If non-'P.Nothing',
    --               this value must be freed with 'GI.Gtk.Structs.SelectionData.selectionDataFree'
    --               when you are finished with it.
clipboardWaitForContents :: a -> Atom -> m (Maybe SelectionData)
clipboardWaitForContents clipboard :: a
clipboard target :: Atom
target = IO (Maybe SelectionData) -> m (Maybe SelectionData)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe SelectionData) -> m (Maybe SelectionData))
-> IO (Maybe SelectionData) -> m (Maybe SelectionData)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Atom
target' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
target
    Ptr SelectionData
result <- Ptr Clipboard -> Ptr Atom -> IO (Ptr SelectionData)
gtk_clipboard_wait_for_contents Ptr Clipboard
clipboard' Ptr Atom
target'
    Maybe SelectionData
maybeResult <- Ptr SelectionData
-> (Ptr SelectionData -> IO SelectionData)
-> IO (Maybe SelectionData)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr SelectionData
result ((Ptr SelectionData -> IO SelectionData)
 -> IO (Maybe SelectionData))
-> (Ptr SelectionData -> IO SelectionData)
-> IO (Maybe SelectionData)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr SelectionData
result' -> do
        SelectionData
result'' <- ((ManagedPtr SelectionData -> SelectionData)
-> Ptr SelectionData -> IO SelectionData
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr SelectionData -> SelectionData
Gtk.SelectionData.SelectionData) Ptr SelectionData
result'
        SelectionData -> IO SelectionData
forall (m :: * -> *) a. Monad m => a -> m a
return SelectionData
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
target
    Maybe SelectionData -> IO (Maybe SelectionData)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SelectionData
maybeResult

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitForContentsMethodInfo
instance (signature ~ (Gdk.Atom.Atom -> m (Maybe Gtk.SelectionData.SelectionData)), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitForContentsMethodInfo a signature where
    overloadedMethod = clipboardWaitForContents

#endif

-- method Clipboard::wait_for_image
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "GdkPixbuf" , name = "Pixbuf" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_for_image" gtk_clipboard_wait_for_image :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Requests the contents of the clipboard as image and converts
-- the result to a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'. This function waits for
-- the data to be received using the main loop, so events,
-- timeouts, etc, may be dispatched during the wait.
-- 
-- /Since: 2.6/
clipboardWaitForImage ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    -- ^ __Returns:__ a newly-allocated t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    --     object which must be disposed with 'GI.GObject.Objects.Object.objectUnref', or
    --     'P.Nothing' if retrieving the selection data failed. (This could
    --     happen for various reasons, in particular if the clipboard
    --     was empty or if the contents of the clipboard could not be
    --     converted into an image.)
clipboardWaitForImage :: a -> m (Maybe Pixbuf)
clipboardWaitForImage clipboard :: a
clipboard = IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Pixbuf) -> m (Maybe Pixbuf))
-> IO (Maybe Pixbuf) -> m (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Pixbuf
result <- Ptr Clipboard -> IO (Ptr Pixbuf)
gtk_clipboard_wait_for_image Ptr Clipboard
clipboard'
    Maybe Pixbuf
maybeResult <- Ptr Pixbuf -> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Pixbuf
result ((Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf))
-> (Ptr Pixbuf -> IO Pixbuf) -> IO (Maybe Pixbuf)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Pixbuf
result' -> do
        Pixbuf
result'' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result'
        Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitForImageMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitForImageMethodInfo a signature where
    overloadedMethod = clipboardWaitForImage

#endif

-- XXX Could not generate method Clipboard::wait_for_rich_text
-- Error was : Not implemented: "Don't know how to allocate \"format\" of type TInterface (Name {namespace = \"Gdk\", name = \"Atom\"})"
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data ClipboardWaitForRichTextMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "waitForRichText" Clipboard) => O.MethodInfo ClipboardWaitForRichTextMethodInfo o p where
    overloadedMethod = undefined
#endif

-- method Clipboard::wait_for_targets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "targets"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gdk" , name = "Atom" })
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location\n          to store an array of targets. The result stored here must\n          be freed with g_free()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferContainer
--           }
--       , Arg
--           { argCName = "n_targets"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "location to store number of items in @targets."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_targets"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "location to store number of items in @targets."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_for_targets" gtk_clipboard_wait_for_targets :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    Ptr (Ptr (Ptr Gdk.Atom.Atom)) ->        -- targets : TCArray False (-1) 2 (TInterface (Name {namespace = "Gdk", name = "Atom"}))
    Ptr Int32 ->                            -- n_targets : TBasicType TInt
    IO CInt

-- | Returns a list of targets that are present on the clipboard, or 'P.Nothing'
-- if there aren’t any targets available. The returned list must be
-- freed with 'GI.GLib.Functions.free'.
-- This function waits for the data to be received using the main
-- loop, so events, timeouts, etc, may be dispatched during the wait.
-- 
-- /Since: 2.4/
clipboardWaitForTargets ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m ((Bool, [Gdk.Atom.Atom]))
    -- ^ __Returns:__ 'P.True' if any targets are present on the clipboard,
    --               otherwise 'P.False'.
clipboardWaitForTargets :: a -> m (Bool, [Atom])
clipboardWaitForTargets clipboard :: a
clipboard = IO (Bool, [Atom]) -> m (Bool, [Atom])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [Atom]) -> m (Bool, [Atom]))
-> IO (Bool, [Atom]) -> m (Bool, [Atom])
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr (Ptr (Ptr Atom))
targets <- IO (Ptr (Ptr (Ptr Atom)))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr (Ptr Gdk.Atom.Atom)))
    Ptr Int32
nTargets <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr Clipboard -> Ptr (Ptr (Ptr Atom)) -> Ptr Int32 -> IO CInt
gtk_clipboard_wait_for_targets Ptr Clipboard
clipboard' Ptr (Ptr (Ptr Atom))
targets Ptr Int32
nTargets
    Int32
nTargets' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nTargets
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Ptr (Ptr Atom)
targets' <- Ptr (Ptr (Ptr Atom)) -> IO (Ptr (Ptr Atom))
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr (Ptr Atom))
targets
    [Ptr Atom]
targets'' <- (Int32 -> Ptr (Ptr Atom) -> IO [Ptr Atom]
forall a b. Integral a => a -> Ptr (Ptr b) -> IO [Ptr b]
unpackPtrArrayWithLength Int32
nTargets') Ptr (Ptr Atom)
targets'
    [Atom]
targets''' <- (Ptr Atom -> IO Atom) -> [Ptr Atom] -> IO [Atom]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Atom -> Atom) -> Ptr Atom -> IO Atom
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Atom -> Atom
Gdk.Atom.Atom) [Ptr Atom]
targets''
    Ptr (Ptr Atom) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Atom)
targets'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Ptr (Ptr (Ptr Atom)) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr (Ptr Atom))
targets
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nTargets
    (Bool, [Atom]) -> IO (Bool, [Atom])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [Atom]
targets''')

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitForTargetsMethodInfo
instance (signature ~ (m ((Bool, [Gdk.Atom.Atom]))), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitForTargetsMethodInfo a signature where
    overloadedMethod = clipboardWaitForTargets

#endif

-- method Clipboard::wait_for_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_for_text" gtk_clipboard_wait_for_text :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO CString

-- | Requests the contents of the clipboard as text and converts
-- the result to UTF-8 if necessary. This function waits for
-- the data to be received using the main loop, so events,
-- timeouts, etc, may be dispatched during the wait.
clipboardWaitForText ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a newly-allocated UTF-8 string which must
    --               be freed with 'GI.GLib.Functions.free', or 'P.Nothing' if retrieving
    --               the selection data failed. (This could happen
    --               for various reasons, in particular if the
    --               clipboard was empty or if the contents of the
    --               clipboard could not be converted into text form.)
clipboardWaitForText :: a -> m (Maybe Text)
clipboardWaitForText clipboard :: a
clipboard = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    CString
result <- Ptr Clipboard -> IO CString
gtk_clipboard_wait_for_text Ptr Clipboard
clipboard'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitForTextMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitForTextMethodInfo a signature where
    overloadedMethod = clipboardWaitForText

#endif

-- method Clipboard::wait_for_uris
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_for_uris" gtk_clipboard_wait_for_uris :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO (Ptr CString)

-- | Requests the contents of the clipboard as URIs. This function waits
-- for the data to be received using the main loop, so events,
-- timeouts, etc, may be dispatched during the wait.
-- 
-- /Since: 2.14/
clipboardWaitForUris ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m (Maybe [T.Text])
    -- ^ __Returns:__ 
    --     a newly-allocated 'P.Nothing'-terminated array of strings which must
    --     be freed with 'GI.GLib.Functions.strfreev', or 'P.Nothing' if retrieving the
    --     selection data failed. (This could happen for various reasons,
    --     in particular if the clipboard was empty or if the contents of
    --     the clipboard could not be converted into URI form.)
clipboardWaitForUris :: a -> m (Maybe [Text])
clipboardWaitForUris clipboard :: a
clipboard = IO (Maybe [Text]) -> m (Maybe [Text])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [Text]) -> m (Maybe [Text]))
-> IO (Maybe [Text]) -> m (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr CString
result <- Ptr Clipboard -> IO (Ptr CString)
gtk_clipboard_wait_for_uris Ptr Clipboard
clipboard'
    Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result'
        [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Maybe [Text] -> IO (Maybe [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitForUrisMethodInfo
instance (signature ~ (m (Maybe [T.Text])), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitForUrisMethodInfo a signature where
    overloadedMethod = clipboardWaitForUris

#endif

-- method Clipboard::wait_is_image_available
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_is_image_available" gtk_clipboard_wait_is_image_available :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO CInt

-- | Test to see if there is an image available to be pasted
-- This is done by requesting the TARGETS atom and checking
-- if it contains any of the supported image targets. This function
-- waits for the data to be received using the main loop, so events,
-- timeouts, etc, may be dispatched during the wait.
-- 
-- This function is a little faster than calling
-- 'GI.Gtk.Objects.Clipboard.clipboardWaitForImage' since it doesn’t need to retrieve
-- the actual image data.
-- 
-- /Since: 2.6/
clipboardWaitIsImageAvailable ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m Bool
    -- ^ __Returns:__ 'P.True' is there is an image available, 'P.False' otherwise.
clipboardWaitIsImageAvailable :: a -> m Bool
clipboardWaitIsImageAvailable clipboard :: a
clipboard = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    CInt
result <- Ptr Clipboard -> IO CInt
gtk_clipboard_wait_is_image_available Ptr Clipboard
clipboard'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitIsImageAvailableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitIsImageAvailableMethodInfo a signature where
    overloadedMethod = clipboardWaitIsImageAvailable

#endif

-- method Clipboard::wait_is_rich_text_available
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextBuffer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextBuffer" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_is_rich_text_available" gtk_clipboard_wait_is_rich_text_available :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    Ptr Gtk.TextBuffer.TextBuffer ->        -- buffer : TInterface (Name {namespace = "Gtk", name = "TextBuffer"})
    IO CInt

-- | Test to see if there is rich text available to be pasted
-- This is done by requesting the TARGETS atom and checking
-- if it contains any of the supported rich text targets. This function
-- waits for the data to be received using the main loop, so events,
-- timeouts, etc, may be dispatched during the wait.
-- 
-- This function is a little faster than calling
-- 'GI.Gtk.Objects.Clipboard.clipboardWaitForRichText' since it doesn’t need to retrieve
-- the actual text.
-- 
-- /Since: 2.10/
clipboardWaitIsRichTextAvailable ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a, Gtk.TextBuffer.IsTextBuffer b) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> b
    -- ^ /@buffer@/: a t'GI.Gtk.Objects.TextBuffer.TextBuffer'
    -> m Bool
    -- ^ __Returns:__ 'P.True' is there is rich text available, 'P.False' otherwise.
clipboardWaitIsRichTextAvailable :: a -> b -> m Bool
clipboardWaitIsRichTextAvailable clipboard :: a
clipboard buffer :: b
buffer = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr TextBuffer
buffer' <- b -> IO (Ptr TextBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
buffer
    CInt
result <- Ptr Clipboard -> Ptr TextBuffer -> IO CInt
gtk_clipboard_wait_is_rich_text_available Ptr Clipboard
clipboard' Ptr TextBuffer
buffer'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
buffer
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitIsRichTextAvailableMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsClipboard a, Gtk.TextBuffer.IsTextBuffer b) => O.MethodInfo ClipboardWaitIsRichTextAvailableMethodInfo a signature where
    overloadedMethod = clipboardWaitIsRichTextAvailable

#endif

-- method Clipboard::wait_is_target_available
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Atom" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A #GdkAtom indicating which target to look for."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_is_target_available" gtk_clipboard_wait_is_target_available :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    Ptr Gdk.Atom.Atom ->                    -- target : TInterface (Name {namespace = "Gdk", name = "Atom"})
    IO CInt

-- | Checks if a clipboard supports pasting data of a given type. This
-- function can be used to determine if a “Paste” menu item should be
-- insensitive or not.
-- 
-- If you want to see if there’s text available on the clipboard, use
-- gtk_clipboard_wait_is_text_available () instead.
-- 
-- /Since: 2.6/
clipboardWaitIsTargetAvailable ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> Gdk.Atom.Atom
    -- ^ /@target@/: A t'GI.Gdk.Structs.Atom.Atom' indicating which target to look for.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the target is available, 'P.False' otherwise.
clipboardWaitIsTargetAvailable :: a -> Atom -> m Bool
clipboardWaitIsTargetAvailable clipboard :: a
clipboard target :: Atom
target = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    Ptr Atom
target' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
target
    CInt
result <- Ptr Clipboard -> Ptr Atom -> IO CInt
gtk_clipboard_wait_is_target_available Ptr Clipboard
clipboard' Ptr Atom
target'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
target
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitIsTargetAvailableMethodInfo
instance (signature ~ (Gdk.Atom.Atom -> m Bool), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitIsTargetAvailableMethodInfo a signature where
    overloadedMethod = clipboardWaitIsTargetAvailable

#endif

-- method Clipboard::wait_is_text_available
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_is_text_available" gtk_clipboard_wait_is_text_available :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO CInt

-- | Test to see if there is text available to be pasted
-- This is done by requesting the TARGETS atom and checking
-- if it contains any of the supported text targets. This function
-- waits for the data to be received using the main loop, so events,
-- timeouts, etc, may be dispatched during the wait.
-- 
-- This function is a little faster than calling
-- 'GI.Gtk.Objects.Clipboard.clipboardWaitForText' since it doesn’t need to retrieve
-- the actual text.
clipboardWaitIsTextAvailable ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m Bool
    -- ^ __Returns:__ 'P.True' is there is text available, 'P.False' otherwise.
clipboardWaitIsTextAvailable :: a -> m Bool
clipboardWaitIsTextAvailable clipboard :: a
clipboard = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    CInt
result <- Ptr Clipboard -> IO CInt
gtk_clipboard_wait_is_text_available Ptr Clipboard
clipboard'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitIsTextAvailableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitIsTextAvailableMethodInfo a signature where
    overloadedMethod = clipboardWaitIsTextAvailable

#endif

-- method Clipboard::wait_is_uris_available
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "clipboard"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Clipboard" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkClipboard" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_wait_is_uris_available" gtk_clipboard_wait_is_uris_available :: 
    Ptr Clipboard ->                        -- clipboard : TInterface (Name {namespace = "Gtk", name = "Clipboard"})
    IO CInt

-- | Test to see if there is a list of URIs available to be pasted
-- This is done by requesting the TARGETS atom and checking
-- if it contains the URI targets. This function
-- waits for the data to be received using the main loop, so events,
-- timeouts, etc, may be dispatched during the wait.
-- 
-- This function is a little faster than calling
-- 'GI.Gtk.Objects.Clipboard.clipboardWaitForUris' since it doesn’t need to retrieve
-- the actual URI data.
-- 
-- /Since: 2.14/
clipboardWaitIsUrisAvailable ::
    (B.CallStack.HasCallStack, MonadIO m, IsClipboard a) =>
    a
    -- ^ /@clipboard@/: a t'GI.Gtk.Objects.Clipboard.Clipboard'
    -> m Bool
    -- ^ __Returns:__ 'P.True' is there is an URI list available, 'P.False' otherwise.
clipboardWaitIsUrisAvailable :: a -> m Bool
clipboardWaitIsUrisAvailable clipboard :: a
clipboard = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clipboard
clipboard' <- a -> IO (Ptr Clipboard)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
clipboard
    CInt
result <- Ptr Clipboard -> IO CInt
gtk_clipboard_wait_is_uris_available Ptr Clipboard
clipboard'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
clipboard
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ClipboardWaitIsUrisAvailableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsClipboard a) => O.MethodInfo ClipboardWaitIsUrisAvailableMethodInfo a signature where
    overloadedMethod = clipboardWaitIsUrisAvailable

#endif

-- method Clipboard::get
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "selection"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Atom" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GdkAtom which identifies the clipboard to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Clipboard" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_get" gtk_clipboard_get :: 
    Ptr Gdk.Atom.Atom ->                    -- selection : TInterface (Name {namespace = "Gdk", name = "Atom"})
    IO (Ptr Clipboard)

-- | Returns the clipboard object for the given selection.
-- See 'GI.Gtk.Objects.Clipboard.clipboardGetForDisplay' for complete details.
clipboardGet ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gdk.Atom.Atom
    -- ^ /@selection@/: a t'GI.Gdk.Structs.Atom.Atom' which identifies the clipboard to use
    -> m Clipboard
    -- ^ __Returns:__ the appropriate clipboard object. If no clipboard
    --     already exists, a new one will be created. Once a clipboard
    --     object has been created, it is persistent and, since it is
    --     owned by GTK+, must not be freed or unreffed.
clipboardGet :: Atom -> m Clipboard
clipboardGet selection :: Atom
selection = IO Clipboard -> m Clipboard
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Clipboard -> m Clipboard) -> IO Clipboard -> m Clipboard
forall a b. (a -> b) -> a -> b
$ do
    Ptr Atom
selection' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
selection
    Ptr Clipboard
result <- Ptr Atom -> IO (Ptr Clipboard)
gtk_clipboard_get Ptr Atom
selection'
    Text -> Ptr Clipboard -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "clipboardGet" Ptr Clipboard
result
    Clipboard
result' <- ((ManagedPtr Clipboard -> Clipboard)
-> Ptr Clipboard -> IO Clipboard
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Clipboard -> Clipboard
Clipboard) Ptr Clipboard
result
    Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
selection
    Clipboard -> IO Clipboard
forall (m :: * -> *) a. Monad m => a -> m a
return Clipboard
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Clipboard::get_default
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GdkDisplay for which the clipboard is to be retrieved."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Clipboard" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_get_default" gtk_clipboard_get_default :: 
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Clipboard)

-- | Returns the default clipboard object for use with cut\/copy\/paste menu items
-- and keyboard shortcuts.
-- 
-- /Since: 3.16/
clipboardGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
    a
    -- ^ /@display@/: the t'GI.Gdk.Objects.Display.Display' for which the clipboard is to be retrieved.
    -> m Clipboard
    -- ^ __Returns:__ the default clipboard object.
clipboardGetDefault :: a -> m Clipboard
clipboardGetDefault display :: a
display = IO Clipboard -> m Clipboard
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Clipboard -> m Clipboard) -> IO Clipboard -> m Clipboard
forall a b. (a -> b) -> a -> b
$ do
    Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
    Ptr Clipboard
result <- Ptr Display -> IO (Ptr Clipboard)
gtk_clipboard_get_default Ptr Display
display'
    Text -> Ptr Clipboard -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "clipboardGetDefault" Ptr Clipboard
result
    Clipboard
result' <- ((ManagedPtr Clipboard -> Clipboard)
-> Ptr Clipboard -> IO Clipboard
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Clipboard -> Clipboard
Clipboard) Ptr Clipboard
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
    Clipboard -> IO Clipboard
forall (m :: * -> *) a. Monad m => a -> m a
return Clipboard
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Clipboard::get_for_display
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #GdkDisplay for which the clipboard is to be retrieved or created."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "selection"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Atom" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GdkAtom which identifies the clipboard to use."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Clipboard" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_clipboard_get_for_display" gtk_clipboard_get_for_display :: 
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr Gdk.Atom.Atom ->                    -- selection : TInterface (Name {namespace = "Gdk", name = "Atom"})
    IO (Ptr Clipboard)

-- | Returns the clipboard object for the given selection.
-- Cut\/copy\/paste menu items and keyboard shortcuts should use
-- the default clipboard, returned by passing @/GDK_SELECTION_CLIPBOARD/@ for /@selection@/.
-- (@/GDK_NONE/@ is supported as a synonym for GDK_SELECTION_CLIPBOARD
-- for backwards compatibility reasons.)
-- The currently-selected object or text should be provided on the clipboard
-- identified by @/GDK_SELECTION_PRIMARY/@. Cut\/copy\/paste menu items
-- conceptually copy the contents of the @/GDK_SELECTION_PRIMARY/@ clipboard
-- to the default clipboard, i.e. they copy the selection to what the
-- user sees as the clipboard.
-- 
-- (Passing @/GDK_NONE/@ is the same as using @gdk_atom_intern
-- (\"CLIPBOARD\", FALSE)@.
-- 
-- See the
-- <http://www.freedesktop.org/Standards/clipboards-spec FreeDesktop Clipboard Specification>
-- for a detailed discussion of the “CLIPBOARD” vs. “PRIMARY”
-- selections under the X window system. On Win32 the
-- @/GDK_SELECTION_PRIMARY/@ clipboard is essentially ignored.)
-- 
-- It’s possible to have arbitrary named clipboards; if you do invent
-- new clipboards, you should prefix the selection name with an
-- underscore (because the ICCCM requires that nonstandard atoms are
-- underscore-prefixed), and namespace it as well. For example,
-- if your application called “Foo” has a special-purpose
-- clipboard, you might call it “_FOO_SPECIAL_CLIPBOARD”.
-- 
-- /Since: 2.2/
clipboardGetForDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
    a
    -- ^ /@display@/: the t'GI.Gdk.Objects.Display.Display' for which the clipboard is to be retrieved or created.
    -> Gdk.Atom.Atom
    -- ^ /@selection@/: a t'GI.Gdk.Structs.Atom.Atom' which identifies the clipboard to use.
    -> m Clipboard
    -- ^ __Returns:__ the appropriate clipboard object. If no
    --   clipboard already exists, a new one will be created. Once a clipboard
    --   object has been created, it is persistent and, since it is owned by
    --   GTK+, must not be freed or unrefd.
clipboardGetForDisplay :: a -> Atom -> m Clipboard
clipboardGetForDisplay display :: a
display selection :: Atom
selection = IO Clipboard -> m Clipboard
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Clipboard -> m Clipboard) -> IO Clipboard -> m Clipboard
forall a b. (a -> b) -> a -> b
$ do
    Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
    Ptr Atom
selection' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
selection
    Ptr Clipboard
result <- Ptr Display -> Ptr Atom -> IO (Ptr Clipboard)
gtk_clipboard_get_for_display Ptr Display
display' Ptr Atom
selection'
    Text -> Ptr Clipboard -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "clipboardGetForDisplay" Ptr Clipboard
result
    Clipboard
result' <- ((ManagedPtr Clipboard -> Clipboard)
-> Ptr Clipboard -> IO Clipboard
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Clipboard -> Clipboard
Clipboard) Ptr Clipboard
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
    Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
selection
    Clipboard -> IO Clipboard
forall (m :: * -> *) a. Monad m => a -> m a
return Clipboard
result'

#if defined(ENABLE_OVERLOADING)
#endif