{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Gtk.Structs.SelectionData
    ( 

-- * Exported types
    SelectionData(..)                       ,
    noSelectionData                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveSelectionDataMethod              ,
#endif


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    SelectionDataCopyMethodInfo             ,
#endif
    selectionDataCopy                       ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    SelectionDataFreeMethodInfo             ,
#endif
    selectionDataFree                       ,


-- ** getData #method:getData#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetDataMethodInfo          ,
#endif
    selectionDataGetData                    ,


-- ** getDataType #method:getDataType#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetDataTypeMethodInfo      ,
#endif
    selectionDataGetDataType                ,


-- ** getDisplay #method:getDisplay#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetDisplayMethodInfo       ,
#endif
    selectionDataGetDisplay                 ,


-- ** getFormat #method:getFormat#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetFormatMethodInfo        ,
#endif
    selectionDataGetFormat                  ,


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetLengthMethodInfo        ,
#endif
    selectionDataGetLength                  ,


-- ** getPixbuf #method:getPixbuf#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetPixbufMethodInfo        ,
#endif
    selectionDataGetPixbuf                  ,


-- ** getSelection #method:getSelection#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetSelectionMethodInfo     ,
#endif
    selectionDataGetSelection               ,


-- ** getTarget #method:getTarget#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetTargetMethodInfo        ,
#endif
    selectionDataGetTarget                  ,


-- ** getTargets #method:getTargets#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetTargetsMethodInfo       ,
#endif
    selectionDataGetTargets                 ,


-- ** getText #method:getText#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetTextMethodInfo          ,
#endif
    selectionDataGetText                    ,


-- ** getUris #method:getUris#

#if defined(ENABLE_OVERLOADING)
    SelectionDataGetUrisMethodInfo          ,
#endif
    selectionDataGetUris                    ,


-- ** set #method:set#

#if defined(ENABLE_OVERLOADING)
    SelectionDataSetMethodInfo              ,
#endif
    selectionDataSet                        ,


-- ** setPixbuf #method:setPixbuf#

#if defined(ENABLE_OVERLOADING)
    SelectionDataSetPixbufMethodInfo        ,
#endif
    selectionDataSetPixbuf                  ,


-- ** setText #method:setText#

#if defined(ENABLE_OVERLOADING)
    SelectionDataSetTextMethodInfo          ,
#endif
    selectionDataSetText                    ,


-- ** setUris #method:setUris#

#if defined(ENABLE_OVERLOADING)
    SelectionDataSetUrisMethodInfo          ,
#endif
    selectionDataSetUris                    ,


-- ** targetsIncludeImage #method:targetsIncludeImage#

#if defined(ENABLE_OVERLOADING)
    SelectionDataTargetsIncludeImageMethodInfo,
#endif
    selectionDataTargetsIncludeImage        ,


-- ** targetsIncludeRichText #method:targetsIncludeRichText#

#if defined(ENABLE_OVERLOADING)
    SelectionDataTargetsIncludeRichTextMethodInfo,
#endif
    selectionDataTargetsIncludeRichText     ,


-- ** targetsIncludeText #method:targetsIncludeText#

#if defined(ENABLE_OVERLOADING)
    SelectionDataTargetsIncludeTextMethodInfo,
#endif
    selectionDataTargetsIncludeText         ,


-- ** targetsIncludeUri #method:targetsIncludeUri#

#if defined(ENABLE_OVERLOADING)
    SelectionDataTargetsIncludeUriMethodInfo,
#endif
    selectionDataTargetsIncludeUri          ,




    ) 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.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Structs.Atom as Gdk.Atom
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextBuffer as Gtk.TextBuffer

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

instance BoxedObject SelectionData where
    boxedType :: SelectionData -> IO GType
boxedType _ = IO GType
c_gtk_selection_data_get_type

-- | Convert 'SelectionData' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue SelectionData where
    toGValue :: SelectionData -> IO GValue
toGValue o :: SelectionData
o = do
        GType
gtype <- IO GType
c_gtk_selection_data_get_type
        SelectionData -> (Ptr SelectionData -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SelectionData
o (GType
-> (GValue -> Ptr SelectionData -> IO ())
-> Ptr SelectionData
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SelectionData -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO SelectionData
fromGValue gv :: GValue
gv = do
        Ptr SelectionData
ptr <- GValue -> IO (Ptr SelectionData)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr SelectionData)
        (ManagedPtr SelectionData -> SelectionData)
-> Ptr SelectionData -> IO SelectionData
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr SelectionData -> SelectionData
SelectionData Ptr SelectionData
ptr
        
    

-- | A convenience alias for `Nothing` :: `Maybe` `SelectionData`.
noSelectionData :: Maybe SelectionData
noSelectionData :: Maybe SelectionData
noSelectionData = Maybe SelectionData
forall a. Maybe a
Nothing


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

-- method SelectionData::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , 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_selection_data_copy" gtk_selection_data_copy :: 
    Ptr SelectionData ->                    -- data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO (Ptr SelectionData)

-- | Makes a copy of a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct and its data.
selectionDataCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@data@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m SelectionData
    -- ^ __Returns:__ a pointer to a copy of /@data@/.
selectionDataCopy :: SelectionData -> m SelectionData
selectionDataCopy data_ :: SelectionData
data_ = IO SelectionData -> m SelectionData
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SelectionData -> m SelectionData)
-> IO SelectionData -> m SelectionData
forall a b. (a -> b) -> a -> b
$ do
    Ptr SelectionData
data_' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
data_
    Ptr SelectionData
result <- Ptr SelectionData -> IO (Ptr SelectionData)
gtk_selection_data_copy Ptr SelectionData
data_'
    Text -> Ptr SelectionData -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "selectionDataCopy" Ptr SelectionData
result
    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
SelectionData) Ptr SelectionData
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
data_
    SelectionData -> IO SelectionData
forall (m :: * -> *) a. Monad m => a -> m a
return SelectionData
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataCopyMethodInfo
instance (signature ~ (m SelectionData), MonadIO m) => O.MethodInfo SelectionDataCopyMethodInfo SelectionData signature where
    overloadedMethod = selectionDataCopy

#endif

-- method SelectionData::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_selection_data_free" gtk_selection_data_free :: 
    Ptr SelectionData ->                    -- data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO ()

-- | Frees a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct returned from
-- 'GI.Gtk.Structs.SelectionData.selectionDataCopy'.
selectionDataFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@data@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m ()
selectionDataFree :: SelectionData -> m ()
selectionDataFree data_ :: SelectionData
data_ = 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 SelectionData
data_' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
data_
    Ptr SelectionData -> IO ()
gtk_selection_data_free Ptr SelectionData
data_'
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
data_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SelectionDataFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo SelectionDataFreeMethodInfo SelectionData signature where
    overloadedMethod = selectionDataFree

#endif

-- method SelectionData::get_data_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Atom" })
-- throws : False
-- Skip return : False

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

-- | Retrieves the data type of the selection.
-- 
-- /Since: 2.14/
selectionDataGetDataType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m Gdk.Atom.Atom
    -- ^ __Returns:__ the data type of the selection.
selectionDataGetDataType :: SelectionData -> m Atom
selectionDataGetDataType selectionData :: SelectionData
selectionData = IO Atom -> m Atom
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Atom -> m Atom) -> IO Atom -> m Atom
forall a b. (a -> b) -> a -> b
$ do
    Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr Atom
result <- Ptr SelectionData -> IO (Ptr Atom)
gtk_selection_data_get_data_type Ptr SelectionData
selectionData'
    Text -> Ptr Atom -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "selectionDataGetDataType" Ptr Atom
result
    Atom
result' <- ((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
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Atom -> IO Atom
forall (m :: * -> *) a. Monad m => a -> m a
return Atom
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetDataTypeMethodInfo
instance (signature ~ (m Gdk.Atom.Atom), MonadIO m) => O.MethodInfo SelectionDataGetDataTypeMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetDataType

#endif

-- method SelectionData::get_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for length of the data segment"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "return location for length of the data segment"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TUInt8))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_selection_data_get_data_with_length" gtk_selection_data_get_data_with_length :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    Ptr Int32 ->                            -- length : TBasicType TInt
    IO (Ptr Word8)

-- | Retrieves the raw data of the selection along with its length.
-- 
-- /Since: 3.0/
selectionDataGetData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m ByteString
    -- ^ __Returns:__ the raw data of the selection
selectionDataGetData :: SelectionData -> m ByteString
selectionDataGetData selectionData :: SelectionData
selectionData = IO ByteString -> m ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr Int32
length_ <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Word8
result <- Ptr SelectionData -> Ptr Int32 -> IO (Ptr Word8)
gtk_selection_data_get_data_with_length Ptr SelectionData
selectionData' Ptr Int32
length_
    Int32
length_' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
length_
    Text -> Ptr Word8 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "selectionDataGetData" Ptr Word8
result
    ByteString
result' <- (Int32 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Int32
length_') Ptr Word8
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
length_
    ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetDataMethodInfo
instance (signature ~ (m ByteString), MonadIO m) => O.MethodInfo SelectionDataGetDataMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetData

#endif

-- method SelectionData::get_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , 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_selection_data_get_display" gtk_selection_data_get_display :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO (Ptr Gdk.Display.Display)

-- | Retrieves the display of the selection.
-- 
-- /Since: 2.14/
selectionDataGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m Gdk.Display.Display
    -- ^ __Returns:__ the display of the selection.
selectionDataGetDisplay :: SelectionData -> m Display
selectionDataGetDisplay selectionData :: SelectionData
selectionData = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr Display
result <- Ptr SelectionData -> IO (Ptr Display)
gtk_selection_data_get_display Ptr SelectionData
selectionData'
    Text -> Ptr Display -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "selectionDataGetDisplay" 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
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Display -> IO Display
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetDisplayMethodInfo
instance (signature ~ (m Gdk.Display.Display), MonadIO m) => O.MethodInfo SelectionDataGetDisplayMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetDisplay

#endif

-- method SelectionData::get_format
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_selection_data_get_format" gtk_selection_data_get_format :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO Int32

-- | Retrieves the format of the selection.
-- 
-- /Since: 2.14/
selectionDataGetFormat ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m Int32
    -- ^ __Returns:__ the format of the selection.
selectionDataGetFormat :: SelectionData -> m Int32
selectionDataGetFormat selectionData :: SelectionData
selectionData = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Int32
result <- Ptr SelectionData -> IO Int32
gtk_selection_data_get_format Ptr SelectionData
selectionData'
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetFormatMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo SelectionDataGetFormatMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetFormat

#endif

-- method SelectionData::get_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_selection_data_get_length" gtk_selection_data_get_length :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO Int32

-- | Retrieves the length of the raw data of the selection.
-- 
-- /Since: 2.14/
selectionDataGetLength ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m Int32
    -- ^ __Returns:__ the length of the data of the selection.
selectionDataGetLength :: SelectionData -> m Int32
selectionDataGetLength selectionData :: SelectionData
selectionData = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Int32
result <- Ptr SelectionData -> IO Int32
gtk_selection_data_get_length Ptr SelectionData
selectionData'
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetLengthMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo SelectionDataGetLengthMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetLength

#endif

-- method SelectionData::get_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData"
--                 , 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_selection_data_get_pixbuf" gtk_selection_data_get_pixbuf :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)

-- | Gets the contents of the selection data as a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'.
-- 
-- /Since: 2.6/
selectionDataGetPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData'
    -> m (Maybe GdkPixbuf.Pixbuf.Pixbuf)
    -- ^ __Returns:__ if the selection data
    --   contained a recognized image type and it could be converted to a
    --   t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf', a newly allocated pixbuf is returned, otherwise
    --   'P.Nothing'.  If the result is non-'P.Nothing' it must be freed with
    --   'GI.GObject.Objects.Object.objectUnref'.
selectionDataGetPixbuf :: SelectionData -> m (Maybe Pixbuf)
selectionDataGetPixbuf selectionData :: SelectionData
selectionData = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr Pixbuf
result <- Ptr SelectionData -> IO (Ptr Pixbuf)
gtk_selection_data_get_pixbuf Ptr SelectionData
selectionData'
    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''
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Maybe Pixbuf -> IO (Maybe Pixbuf)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Pixbuf
maybeResult

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetPixbufMethodInfo
instance (signature ~ (m (Maybe GdkPixbuf.Pixbuf.Pixbuf)), MonadIO m) => O.MethodInfo SelectionDataGetPixbufMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetPixbuf

#endif

-- method SelectionData::get_selection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Atom" })
-- throws : False
-- Skip return : False

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

-- | Retrieves the selection t'GI.Gdk.Structs.Atom.Atom' of the selection data.
-- 
-- /Since: 2.16/
selectionDataGetSelection ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m Gdk.Atom.Atom
    -- ^ __Returns:__ the selection t'GI.Gdk.Structs.Atom.Atom' of the selection data.
selectionDataGetSelection :: SelectionData -> m Atom
selectionDataGetSelection selectionData :: SelectionData
selectionData = IO Atom -> m Atom
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Atom -> m Atom) -> IO Atom -> m Atom
forall a b. (a -> b) -> a -> b
$ do
    Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr Atom
result <- Ptr SelectionData -> IO (Ptr Atom)
gtk_selection_data_get_selection Ptr SelectionData
selectionData'
    Text -> Ptr Atom -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "selectionDataGetSelection" Ptr Atom
result
    Atom
result' <- ((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
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Atom -> IO Atom
forall (m :: * -> *) a. Monad m => a -> m a
return Atom
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetSelectionMethodInfo
instance (signature ~ (m Gdk.Atom.Atom), MonadIO m) => O.MethodInfo SelectionDataGetSelectionMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetSelection

#endif

-- method SelectionData::get_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Atom" })
-- throws : False
-- Skip return : False

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

-- | Retrieves the target of the selection.
-- 
-- /Since: 2.14/
selectionDataGetTarget ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> m Gdk.Atom.Atom
    -- ^ __Returns:__ the target of the selection.
selectionDataGetTarget :: SelectionData -> m Atom
selectionDataGetTarget selectionData :: SelectionData
selectionData = IO Atom -> m Atom
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Atom -> m Atom) -> IO Atom -> m Atom
forall a b. (a -> b) -> a -> b
$ do
    Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr Atom
result <- Ptr SelectionData -> IO (Ptr Atom)
gtk_selection_data_get_target Ptr SelectionData
selectionData'
    Text -> Ptr Atom -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "selectionDataGetTarget" Ptr Atom
result
    Atom
result' <- ((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
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Atom -> IO Atom
forall (m :: * -> *) a. Monad m => a -> m a
return Atom
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetTargetMethodInfo
instance (signature ~ (m Gdk.Atom.Atom), MonadIO m) => O.MethodInfo SelectionDataGetTargetMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetTarget

#endif

-- method SelectionData::get_targets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData object"
--                 , 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
--                       "\n          location to store an array of targets. The result stored\n          here must be freed with g_free()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferContainer
--           }
--       , Arg
--           { argCName = "n_atoms"
--           , 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_atoms"
--              , 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_selection_data_get_targets" gtk_selection_data_get_targets :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    Ptr (Ptr (Ptr Gdk.Atom.Atom)) ->        -- targets : TCArray False (-1) 2 (TInterface (Name {namespace = "Gdk", name = "Atom"}))
    Ptr Int32 ->                            -- n_atoms : TBasicType TInt
    IO CInt

-- | Gets the contents of /@selectionData@/ as an array of targets.
-- This can be used to interpret the results of getting
-- the standard TARGETS target that is always supplied for
-- any selection.
selectionDataGetTargets ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData' object
    -> m ((Bool, [Gdk.Atom.Atom]))
    -- ^ __Returns:__ 'P.True' if /@selectionData@/ contains a valid
    --    array of targets, otherwise 'P.False'.
selectionDataGetTargets :: SelectionData -> m (Bool, [Atom])
selectionDataGetTargets selectionData :: SelectionData
selectionData = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    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
nAtoms <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr SelectionData -> Ptr (Ptr (Ptr Atom)) -> Ptr Int32 -> IO CInt
gtk_selection_data_get_targets Ptr SelectionData
selectionData' Ptr (Ptr (Ptr Atom))
targets Ptr Int32
nAtoms
    Int32
nAtoms' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nAtoms
    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
nAtoms') 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'
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    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
nAtoms
    (Bool, [Atom]) -> IO (Bool, [Atom])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [Atom]
targets''')

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetTargetsMethodInfo
instance (signature ~ (m ((Bool, [Gdk.Atom.Atom]))), MonadIO m) => O.MethodInfo SelectionDataGetTargetsMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetTargets

#endif

-- method SelectionData::get_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData"
--                 , 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_selection_data_get_text" gtk_selection_data_get_text :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO CString

-- | Gets the contents of the selection data as a UTF-8 string.
selectionDataGetText ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ if the selection data contained a
    --   recognized text type and it could be converted to UTF-8, a newly
    --   allocated string containing the converted text, otherwise 'P.Nothing'.
    --   If the result is non-'P.Nothing' it must be freed with 'GI.GLib.Functions.free'.
selectionDataGetText :: SelectionData -> m (Maybe Text)
selectionDataGetText selectionData :: SelectionData
selectionData = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    CString
result <- Ptr SelectionData -> IO CString
gtk_selection_data_get_text Ptr SelectionData
selectionData'
    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''
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetTextMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.MethodInfo SelectionDataGetTextMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetText

#endif

-- method SelectionData::get_uris
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData"
--                 , 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_selection_data_get_uris" gtk_selection_data_get_uris :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO (Ptr CString)

-- | Gets the contents of the selection data as array of URIs.
-- 
-- /Since: 2.6/
selectionDataGetUris ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData'
    -> m [T.Text]
    -- ^ __Returns:__ if
    --   the selection data contains a list of
    --   URIs, a newly allocated 'P.Nothing'-terminated string array
    --   containing the URIs, otherwise 'P.Nothing'. If the result is
    --   non-'P.Nothing' it must be freed with 'GI.GLib.Functions.strfreev'.
selectionDataGetUris :: SelectionData -> m [Text]
selectionDataGetUris selectionData :: SelectionData
selectionData = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr CString
result <- Ptr SelectionData -> IO (Ptr CString)
gtk_selection_data_get_uris Ptr SelectionData
selectionData'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "selectionDataGetUris" Ptr CString
result
    [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
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataGetUrisMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.MethodInfo SelectionDataGetUrisMethodInfo SelectionData signature where
    overloadedMethod = selectionDataGetUris

#endif

-- method SelectionData::set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer to a #GtkSelectionData-struct."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Atom" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the type of selection data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "format"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "format (number of bits in a unit)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TCArray False (-1) 4 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the data (will be copied)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of the data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of the data" , sinceVersion = Nothing }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_selection_data_set" gtk_selection_data_set :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    Ptr Gdk.Atom.Atom ->                    -- type : TInterface (Name {namespace = "Gdk", name = "Atom"})
    Int32 ->                                -- format : TBasicType TInt
    Ptr Word8 ->                            -- data : TCArray False (-1) 4 (TBasicType TUInt8)
    Int32 ->                                -- length : TBasicType TInt
    IO ()

-- | Stores new data into a t'GI.Gtk.Structs.SelectionData.SelectionData' object. Should
-- only be called from a selection handler callback.
-- Zero-terminates the stored data.
selectionDataSet ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a pointer to a t'GI.Gtk.Structs.SelectionData.SelectionData'-struct.
    -> Gdk.Atom.Atom
    -- ^ /@type@/: the type of selection data
    -> Int32
    -- ^ /@format@/: format (number of bits in a unit)
    -> ByteString
    -- ^ /@data@/: pointer to the data (will be copied)
    -> m ()
selectionDataSet :: SelectionData -> Atom -> Int32 -> ByteString -> m ()
selectionDataSet selectionData :: SelectionData
selectionData type_ :: Atom
type_ format :: Int32
format data_ :: ByteString
data_ = 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 length_ :: Int32
length_ = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
data_
    Ptr SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr Atom
type_' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
type_
    Ptr Word8
data_' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
data_
    Ptr SelectionData
-> Ptr Atom -> Int32 -> Ptr Word8 -> Int32 -> IO ()
gtk_selection_data_set Ptr SelectionData
selectionData' Ptr Atom
type_' Int32
format Ptr Word8
data_' Int32
length_
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
type_
    Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
data_'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SelectionDataSetMethodInfo
instance (signature ~ (Gdk.Atom.Atom -> Int32 -> ByteString -> m ()), MonadIO m) => O.MethodInfo SelectionDataSetMethodInfo SelectionData signature where
    overloadedMethod = selectionDataSet

#endif

-- method SelectionData::set_pixbuf
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData"
--                 , 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: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_selection_data_set_pixbuf" gtk_selection_data_set_pixbuf :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    Ptr GdkPixbuf.Pixbuf.Pixbuf ->          -- pixbuf : TInterface (Name {namespace = "GdkPixbuf", name = "Pixbuf"})
    IO CInt

-- | Sets the contents of the selection from a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
-- The pixbuf is converted to the form determined by
-- /@selectionData@/->target.
-- 
-- /Since: 2.6/
selectionDataSetPixbuf ::
    (B.CallStack.HasCallStack, MonadIO m, GdkPixbuf.Pixbuf.IsPixbuf a) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData'
    -> a
    -- ^ /@pixbuf@/: a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the selection was successfully set,
    --   otherwise 'P.False'.
selectionDataSetPixbuf :: SelectionData -> a -> m Bool
selectionDataSetPixbuf selectionData :: SelectionData
selectionData pixbuf :: a
pixbuf = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr Pixbuf
pixbuf' <- a -> IO (Ptr Pixbuf)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pixbuf
    CInt
result <- Ptr SelectionData -> Ptr Pixbuf -> IO CInt
gtk_selection_data_set_pixbuf Ptr SelectionData
selectionData' Ptr Pixbuf
pixbuf'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pixbuf
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataSetPixbufMethodInfo
instance (signature ~ (a -> m Bool), MonadIO m, GdkPixbuf.Pixbuf.IsPixbuf a) => O.MethodInfo SelectionDataSetPixbufMethodInfo SelectionData signature where
    overloadedMethod = selectionDataSetPixbuf

#endif

-- method SelectionData::set_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "str"
--           , 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 "the length of @str, or -1 if @str is nul-terminated."
--                 , 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_selection_data_set_text" gtk_selection_data_set_text :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    CString ->                              -- str : TBasicType TUTF8
    Int32 ->                                -- len : TBasicType TInt
    IO CInt

-- | Sets the contents of the selection from a UTF-8 encoded string.
-- The string is converted to the form determined by
-- /@selectionData@/->target.
selectionDataSetText ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData'
    -> T.Text
    -- ^ /@str@/: a UTF-8 string
    -> Int32
    -- ^ /@len@/: the length of /@str@/, or -1 if /@str@/ is nul-terminated.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the selection was successfully set,
    --   otherwise 'P.False'.
selectionDataSetText :: SelectionData -> Text -> Int32 -> m Bool
selectionDataSetText selectionData :: SelectionData
selectionData str :: Text
str len :: Int32
len = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    CString
str' <- Text -> IO CString
textToCString Text
str
    CInt
result <- Ptr SelectionData -> CString -> Int32 -> IO CInt
gtk_selection_data_set_text Ptr SelectionData
selectionData' CString
str' Int32
len
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataSetTextMethodInfo
instance (signature ~ (T.Text -> Int32 -> m Bool), MonadIO m) => O.MethodInfo SelectionDataSetTextMethodInfo SelectionData signature where
    overloadedMethod = selectionDataSetText

#endif

-- method SelectionData::set_uris
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uris"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a %NULL-terminated array of\n    strings holding URIs"
--                 , 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_selection_data_set_uris" gtk_selection_data_set_uris :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    Ptr CString ->                          -- uris : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO CInt

-- | Sets the contents of the selection from a list of URIs.
-- The string is converted to the form determined by
-- /@selectionData@/->target.
-- 
-- /Since: 2.6/
selectionDataSetUris ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData'
    -> [T.Text]
    -- ^ /@uris@/: a 'P.Nothing'-terminated array of
    --     strings holding URIs
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the selection was successfully set,
    --   otherwise 'P.False'.
selectionDataSetUris :: SelectionData -> [Text] -> m Bool
selectionDataSetUris selectionData :: SelectionData
selectionData uris :: [Text]
uris = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr CString
uris' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
uris
    CInt
result <- Ptr SelectionData -> Ptr CString -> IO CInt
gtk_selection_data_set_uris Ptr SelectionData
selectionData' Ptr CString
uris'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    (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
uris'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
uris'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataSetUrisMethodInfo
instance (signature ~ ([T.Text] -> m Bool), MonadIO m) => O.MethodInfo SelectionDataSetUrisMethodInfo SelectionData signature where
    overloadedMethod = selectionDataSetUris

#endif

-- method SelectionData::targets_include_image
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "writable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "whether to accept only targets for which GTK+ knows\n  how to convert a pixbuf into the format"
--                 , 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_selection_data_targets_include_image" gtk_selection_data_targets_include_image :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    CInt ->                                 -- writable : TBasicType TBoolean
    IO CInt

-- | Given a t'GI.Gtk.Structs.SelectionData.SelectionData' object holding a list of targets,
-- determines if any of the targets in /@targets@/ can be used to
-- provide a t'GI.GdkPixbuf.Objects.Pixbuf.Pixbuf'.
-- 
-- /Since: 2.6/
selectionDataTargetsIncludeImage ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData' object
    -> Bool
    -- ^ /@writable@/: whether to accept only targets for which GTK+ knows
    --   how to convert a pixbuf into the format
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@selectionData@/ holds a list of targets,
    --   and a suitable target for images is included, otherwise 'P.False'.
selectionDataTargetsIncludeImage :: SelectionData -> Bool -> m Bool
selectionDataTargetsIncludeImage selectionData :: SelectionData
selectionData writable :: Bool
writable = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    let writable' :: CInt
writable' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
writable
    CInt
result <- Ptr SelectionData -> CInt -> IO CInt
gtk_selection_data_targets_include_image Ptr SelectionData
selectionData' CInt
writable'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataTargetsIncludeImageMethodInfo
instance (signature ~ (Bool -> m Bool), MonadIO m) => O.MethodInfo SelectionDataTargetsIncludeImageMethodInfo SelectionData signature where
    overloadedMethod = selectionDataTargetsIncludeImage

#endif

-- method SelectionData::targets_include_rich_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData object"
--                 , 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_selection_data_targets_include_rich_text" gtk_selection_data_targets_include_rich_text :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    Ptr Gtk.TextBuffer.TextBuffer ->        -- buffer : TInterface (Name {namespace = "Gtk", name = "TextBuffer"})
    IO CInt

-- | Given a t'GI.Gtk.Structs.SelectionData.SelectionData' object holding a list of targets,
-- determines if any of the targets in /@targets@/ can be used to
-- provide rich text.
-- 
-- /Since: 2.10/
selectionDataTargetsIncludeRichText ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.TextBuffer.IsTextBuffer a) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData' object
    -> a
    -- ^ /@buffer@/: a t'GI.Gtk.Objects.TextBuffer.TextBuffer'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@selectionData@/ holds a list of targets,
    --               and a suitable target for rich text is included,
    --               otherwise 'P.False'.
selectionDataTargetsIncludeRichText :: SelectionData -> a -> m Bool
selectionDataTargetsIncludeRichText selectionData :: SelectionData
selectionData buffer :: a
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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    Ptr TextBuffer
buffer' <- a -> IO (Ptr TextBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buffer
    CInt
result <- Ptr SelectionData -> Ptr TextBuffer -> IO CInt
gtk_selection_data_targets_include_rich_text Ptr SelectionData
selectionData' Ptr TextBuffer
buffer'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buffer
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataTargetsIncludeRichTextMethodInfo
instance (signature ~ (a -> m Bool), MonadIO m, Gtk.TextBuffer.IsTextBuffer a) => O.MethodInfo SelectionDataTargetsIncludeRichTextMethodInfo SelectionData signature where
    overloadedMethod = selectionDataTargetsIncludeRichText

#endif

-- method SelectionData::targets_include_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData object"
--                 , 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_selection_data_targets_include_text" gtk_selection_data_targets_include_text :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO CInt

-- | Given a t'GI.Gtk.Structs.SelectionData.SelectionData' object holding a list of targets,
-- determines if any of the targets in /@targets@/ can be used to
-- provide text.
selectionDataTargetsIncludeText ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData' object
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@selectionData@/ holds a list of targets,
    --   and a suitable target for text is included, otherwise 'P.False'.
selectionDataTargetsIncludeText :: SelectionData -> m Bool
selectionDataTargetsIncludeText selectionData :: SelectionData
selectionData = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    CInt
result <- Ptr SelectionData -> IO CInt
gtk_selection_data_targets_include_text Ptr SelectionData
selectionData'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataTargetsIncludeTextMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo SelectionDataTargetsIncludeTextMethodInfo SelectionData signature where
    overloadedMethod = selectionDataTargetsIncludeText

#endif

-- method SelectionData::targets_include_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "selection_data"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SelectionData" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSelectionData object"
--                 , 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_selection_data_targets_include_uri" gtk_selection_data_targets_include_uri :: 
    Ptr SelectionData ->                    -- selection_data : TInterface (Name {namespace = "Gtk", name = "SelectionData"})
    IO CInt

-- | Given a t'GI.Gtk.Structs.SelectionData.SelectionData' object holding a list of targets,
-- determines if any of the targets in /@targets@/ can be used to
-- provide a list or URIs.
-- 
-- /Since: 2.10/
selectionDataTargetsIncludeUri ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SelectionData
    -- ^ /@selectionData@/: a t'GI.Gtk.Structs.SelectionData.SelectionData' object
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@selectionData@/ holds a list of targets,
    --   and a suitable target for URI lists is included, otherwise 'P.False'.
selectionDataTargetsIncludeUri :: SelectionData -> m Bool
selectionDataTargetsIncludeUri selectionData :: SelectionData
selectionData = 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 SelectionData
selectionData' <- SelectionData -> IO (Ptr SelectionData)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SelectionData
selectionData
    CInt
result <- Ptr SelectionData -> IO CInt
gtk_selection_data_targets_include_uri Ptr SelectionData
selectionData'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    SelectionData -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SelectionData
selectionData
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SelectionDataTargetsIncludeUriMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo SelectionDataTargetsIncludeUriMethodInfo SelectionData signature where
    overloadedMethod = selectionDataTargetsIncludeUri

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveSelectionDataMethod (t :: Symbol) (o :: *) :: * where
    ResolveSelectionDataMethod "copy" o = SelectionDataCopyMethodInfo
    ResolveSelectionDataMethod "free" o = SelectionDataFreeMethodInfo
    ResolveSelectionDataMethod "set" o = SelectionDataSetMethodInfo
    ResolveSelectionDataMethod "targetsIncludeImage" o = SelectionDataTargetsIncludeImageMethodInfo
    ResolveSelectionDataMethod "targetsIncludeRichText" o = SelectionDataTargetsIncludeRichTextMethodInfo
    ResolveSelectionDataMethod "targetsIncludeText" o = SelectionDataTargetsIncludeTextMethodInfo
    ResolveSelectionDataMethod "targetsIncludeUri" o = SelectionDataTargetsIncludeUriMethodInfo
    ResolveSelectionDataMethod "getDataType" o = SelectionDataGetDataTypeMethodInfo
    ResolveSelectionDataMethod "getData" o = SelectionDataGetDataMethodInfo
    ResolveSelectionDataMethod "getDisplay" o = SelectionDataGetDisplayMethodInfo
    ResolveSelectionDataMethod "getFormat" o = SelectionDataGetFormatMethodInfo
    ResolveSelectionDataMethod "getLength" o = SelectionDataGetLengthMethodInfo
    ResolveSelectionDataMethod "getPixbuf" o = SelectionDataGetPixbufMethodInfo
    ResolveSelectionDataMethod "getSelection" o = SelectionDataGetSelectionMethodInfo
    ResolveSelectionDataMethod "getTarget" o = SelectionDataGetTargetMethodInfo
    ResolveSelectionDataMethod "getTargets" o = SelectionDataGetTargetsMethodInfo
    ResolveSelectionDataMethod "getText" o = SelectionDataGetTextMethodInfo
    ResolveSelectionDataMethod "getUris" o = SelectionDataGetUrisMethodInfo
    ResolveSelectionDataMethod "setPixbuf" o = SelectionDataSetPixbufMethodInfo
    ResolveSelectionDataMethod "setText" o = SelectionDataSetTextMethodInfo
    ResolveSelectionDataMethod "setUris" o = SelectionDataSetUrisMethodInfo
    ResolveSelectionDataMethod l o = O.MethodResolutionFailed l o

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

#endif