{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gtk.Structs.TargetList.TargetList'-struct is a reference counted list
-- of t'GI.Gtk.Structs.TargetPair.TargetPair' and should be treated as
-- opaque.

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

module GI.Gtk.Structs.TargetList
    ( 

-- * Exported types
    TargetList(..)                          ,
    noTargetList                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveTargetListMethod                 ,
#endif


-- ** add #method:add#

#if defined(ENABLE_OVERLOADING)
    TargetListAddMethodInfo                 ,
#endif
    targetListAdd                           ,


-- ** addImageTargets #method:addImageTargets#

#if defined(ENABLE_OVERLOADING)
    TargetListAddImageTargetsMethodInfo     ,
#endif
    targetListAddImageTargets               ,


-- ** addRichTextTargets #method:addRichTextTargets#

#if defined(ENABLE_OVERLOADING)
    TargetListAddRichTextTargetsMethodInfo  ,
#endif
    targetListAddRichTextTargets            ,


-- ** addTable #method:addTable#

#if defined(ENABLE_OVERLOADING)
    TargetListAddTableMethodInfo            ,
#endif
    targetListAddTable                      ,


-- ** addTextTargets #method:addTextTargets#

#if defined(ENABLE_OVERLOADING)
    TargetListAddTextTargetsMethodInfo      ,
#endif
    targetListAddTextTargets                ,


-- ** addUriTargets #method:addUriTargets#

#if defined(ENABLE_OVERLOADING)
    TargetListAddUriTargetsMethodInfo       ,
#endif
    targetListAddUriTargets                 ,


-- ** find #method:find#

#if defined(ENABLE_OVERLOADING)
    TargetListFindMethodInfo                ,
#endif
    targetListFind                          ,


-- ** new #method:new#

    targetListNew                           ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    TargetListRefMethodInfo                 ,
#endif
    targetListRef                           ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    TargetListRemoveMethodInfo              ,
#endif
    targetListRemove                        ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    TargetListUnrefMethodInfo               ,
#endif
    targetListUnref                         ,




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

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

instance BoxedObject TargetList where
    boxedType :: TargetList -> IO GType
boxedType _ = IO GType
c_gtk_target_list_get_type

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

-- | A convenience alias for `Nothing` :: `Maybe` `TargetList`.
noTargetList :: Maybe TargetList
noTargetList :: Maybe TargetList
noTargetList = Maybe TargetList
forall a. Maybe a
Nothing


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

-- method TargetList::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "targets"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 1
--                 (TInterface Name { namespace = "Gtk" , name = "TargetEntry" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Pointer to an array\n  of #GtkTargetEntry"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ntargets"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of entries in @targets."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "ntargets"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of entries in @targets."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "TargetList" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_new" gtk_target_list_new :: 
    Ptr Gtk.TargetEntry.TargetEntry ->      -- targets : TCArray False (-1) 1 (TInterface (Name {namespace = "Gtk", name = "TargetEntry"}))
    Word32 ->                               -- ntargets : TBasicType TUInt
    IO (Ptr TargetList)

-- | Creates a new t'GI.Gtk.Structs.TargetList.TargetList' from an array of t'GI.Gtk.Structs.TargetEntry.TargetEntry'.
targetListNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe ([Gtk.TargetEntry.TargetEntry])
    -- ^ /@targets@/: Pointer to an array
    --   of t'GI.Gtk.Structs.TargetEntry.TargetEntry'
    -> m TargetList
    -- ^ __Returns:__ the new t'GI.Gtk.Structs.TargetList.TargetList'.
targetListNew :: Maybe [TargetEntry] -> m TargetList
targetListNew targets :: Maybe [TargetEntry]
targets = IO TargetList -> m TargetList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TargetList -> m TargetList) -> IO TargetList -> m TargetList
forall a b. (a -> b) -> a -> b
$ do
    let ntargets :: Word32
ntargets = case Maybe [TargetEntry]
targets of
            Nothing -> 0
            Just jTargets :: [TargetEntry]
jTargets -> Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [TargetEntry] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TargetEntry]
jTargets
    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 TargetList
result <- Ptr TargetEntry -> Word32 -> IO (Ptr TargetList)
gtk_target_list_new Ptr TargetEntry
maybeTargets Word32
ntargets
    Text -> Ptr TargetList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "targetListNew" Ptr TargetList
result
    TargetList
result' <- ((ManagedPtr TargetList -> TargetList)
-> Ptr TargetList -> IO TargetList
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TargetList -> TargetList
TargetList) Ptr TargetList
result
    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
    TargetList -> IO TargetList
forall (m :: * -> *) a. Monad m => a -> m a
return TargetList
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method TargetList::add
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TargetList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTargetList" , 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 "the interned atom representing the target"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the flags for this target"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an ID that will be passed back to the application"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_add" gtk_target_list_add :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    Ptr Gdk.Atom.Atom ->                    -- target : TInterface (Name {namespace = "Gdk", name = "Atom"})
    Word32 ->                               -- flags : TBasicType TUInt
    Word32 ->                               -- info : TBasicType TUInt
    IO ()

-- | Appends another target to a t'GI.Gtk.Structs.TargetList.TargetList'.
targetListAdd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> Gdk.Atom.Atom
    -- ^ /@target@/: the interned atom representing the target
    -> Word32
    -- ^ /@flags@/: the flags for this target
    -> Word32
    -- ^ /@info@/: an ID that will be passed back to the application
    -> m ()
targetListAdd :: TargetList -> Atom -> Word32 -> Word32 -> m ()
targetListAdd list :: TargetList
list target :: Atom
target flags :: Word32
flags info :: Word32
info = 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 TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    Ptr Atom
target' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
target
    Ptr TargetList -> Ptr Atom -> Word32 -> Word32 -> IO ()
gtk_target_list_add Ptr TargetList
list' Ptr Atom
target' Word32
flags Word32
info
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    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 TargetListAddMethodInfo
instance (signature ~ (Gdk.Atom.Atom -> Word32 -> Word32 -> m ()), MonadIO m) => O.MethodInfo TargetListAddMethodInfo TargetList signature where
    overloadedMethod = targetListAdd

#endif

-- method TargetList::add_image_targets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TargetList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTargetList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an ID that will be passed back to the application"
--                 , 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 add 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: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_add_image_targets" gtk_target_list_add_image_targets :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    Word32 ->                               -- info : TBasicType TUInt
    CInt ->                                 -- writable : TBasicType TBoolean
    IO ()

-- | Appends the image targets supported by t'GI.Gtk.Structs.SelectionData.SelectionData' to
-- the target list. All targets are added with the same /@info@/.
-- 
-- /Since: 2.6/
targetListAddImageTargets ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> Word32
    -- ^ /@info@/: an ID that will be passed back to the application
    -> Bool
    -- ^ /@writable@/: whether to add only targets for which GTK+ knows
    --   how to convert a pixbuf into the format
    -> m ()
targetListAddImageTargets :: TargetList -> Word32 -> Bool -> m ()
targetListAddImageTargets list :: TargetList
list info :: Word32
info writable :: Bool
writable = 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 TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    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
    Ptr TargetList -> Word32 -> CInt -> IO ()
gtk_target_list_add_image_targets Ptr TargetList
list' Word32
info CInt
writable'
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TargetListAddImageTargetsMethodInfo
instance (signature ~ (Word32 -> Bool -> m ()), MonadIO m) => O.MethodInfo TargetListAddImageTargetsMethodInfo TargetList signature where
    overloadedMethod = targetListAddImageTargets

#endif

-- method TargetList::add_rich_text_targets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TargetList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTargetList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an ID that will be passed back to the application"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "deserializable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "if %TRUE, then deserializable rich text formats\n                 will be added, serializable formats otherwise."
--                 , 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: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_add_rich_text_targets" gtk_target_list_add_rich_text_targets :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    Word32 ->                               -- info : TBasicType TUInt
    CInt ->                                 -- deserializable : TBasicType TBoolean
    Ptr Gtk.TextBuffer.TextBuffer ->        -- buffer : TInterface (Name {namespace = "Gtk", name = "TextBuffer"})
    IO ()

-- | Appends the rich text targets registered with
-- 'GI.Gtk.Objects.TextBuffer.textBufferRegisterSerializeFormat' or
-- 'GI.Gtk.Objects.TextBuffer.textBufferRegisterDeserializeFormat' to the target list. All
-- targets are added with the same /@info@/.
-- 
-- /Since: 2.10/
targetListAddRichTextTargets ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.TextBuffer.IsTextBuffer a) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> Word32
    -- ^ /@info@/: an ID that will be passed back to the application
    -> Bool
    -- ^ /@deserializable@/: if 'P.True', then deserializable rich text formats
    --                  will be added, serializable formats otherwise.
    -> a
    -- ^ /@buffer@/: a t'GI.Gtk.Objects.TextBuffer.TextBuffer'.
    -> m ()
targetListAddRichTextTargets :: TargetList -> Word32 -> Bool -> a -> m ()
targetListAddRichTextTargets list :: TargetList
list info :: Word32
info deserializable :: Bool
deserializable buffer :: a
buffer = 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 TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    let deserializable' :: CInt
deserializable' = (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
deserializable
    Ptr TextBuffer
buffer' <- a -> IO (Ptr TextBuffer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
buffer
    Ptr TargetList -> Word32 -> CInt -> Ptr TextBuffer -> IO ()
gtk_target_list_add_rich_text_targets Ptr TargetList
list' Word32
info CInt
deserializable' Ptr TextBuffer
buffer'
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
buffer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TargetListAddRichTextTargetsMethodInfo
instance (signature ~ (Word32 -> Bool -> a -> m ()), MonadIO m, Gtk.TextBuffer.IsTextBuffer a) => O.MethodInfo TargetListAddRichTextTargetsMethodInfo TargetList signature where
    overloadedMethod = targetListAddRichTextTargets

#endif

-- method TargetList::add_table
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TargetList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTargetList" , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the table of #GtkTargetEntry"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ntargets"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of targets in the table"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "ntargets"
--              , argType = TBasicType TUInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of targets in the table"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_add_table" gtk_target_list_add_table :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    Ptr Gtk.TargetEntry.TargetEntry ->      -- targets : TCArray False (-1) 2 (TInterface (Name {namespace = "Gtk", name = "TargetEntry"}))
    Word32 ->                               -- ntargets : TBasicType TUInt
    IO ()

-- | Prepends a table of t'GI.Gtk.Structs.TargetEntry.TargetEntry' to a target list.
targetListAddTable ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> [Gtk.TargetEntry.TargetEntry]
    -- ^ /@targets@/: the table of t'GI.Gtk.Structs.TargetEntry.TargetEntry'
    -> m ()
targetListAddTable :: TargetList -> [TargetEntry] -> m ()
targetListAddTable list :: TargetList
list targets :: [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 :: Word32
ntargets = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [TargetEntry] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TargetEntry]
targets
    Ptr TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    [Ptr TargetEntry]
targets' <- (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]
targets
    Ptr TargetEntry
targets'' <- Int -> [Ptr TargetEntry] -> IO (Ptr TargetEntry)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 16 [Ptr TargetEntry]
targets'
    Ptr TargetList -> Ptr TargetEntry -> Word32 -> IO ()
gtk_target_list_add_table Ptr TargetList
list' Ptr TargetEntry
targets'' Word32
ntargets
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    (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 [TargetEntry]
targets
    Ptr TargetEntry -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr TargetEntry
targets''
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TargetListAddTableMethodInfo
instance (signature ~ ([Gtk.TargetEntry.TargetEntry] -> m ()), MonadIO m) => O.MethodInfo TargetListAddTableMethodInfo TargetList signature where
    overloadedMethod = targetListAddTable

#endif

-- method TargetList::add_text_targets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TargetList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTargetList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an ID that will be passed back to the application"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_add_text_targets" gtk_target_list_add_text_targets :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    Word32 ->                               -- info : TBasicType TUInt
    IO ()

-- | Appends the text targets supported by t'GI.Gtk.Structs.SelectionData.SelectionData' to
-- the target list. All targets are added with the same /@info@/.
-- 
-- /Since: 2.6/
targetListAddTextTargets ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> Word32
    -- ^ /@info@/: an ID that will be passed back to the application
    -> m ()
targetListAddTextTargets :: TargetList -> Word32 -> m ()
targetListAddTextTargets list :: TargetList
list info :: Word32
info = 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 TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    Ptr TargetList -> Word32 -> IO ()
gtk_target_list_add_text_targets Ptr TargetList
list' Word32
info
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TargetListAddTextTargetsMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.MethodInfo TargetListAddTextTargetsMethodInfo TargetList signature where
    overloadedMethod = targetListAddTextTargets

#endif

-- method TargetList::add_uri_targets
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TargetList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTargetList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an ID that will be passed back to the application"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_add_uri_targets" gtk_target_list_add_uri_targets :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    Word32 ->                               -- info : TBasicType TUInt
    IO ()

-- | Appends the URI targets supported by t'GI.Gtk.Structs.SelectionData.SelectionData' to
-- the target list. All targets are added with the same /@info@/.
-- 
-- /Since: 2.6/
targetListAddUriTargets ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> Word32
    -- ^ /@info@/: an ID that will be passed back to the application
    -> m ()
targetListAddUriTargets :: TargetList -> Word32 -> m ()
targetListAddUriTargets list :: TargetList
list info :: Word32
info = 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 TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    Ptr TargetList -> Word32 -> IO ()
gtk_target_list_add_uri_targets Ptr TargetList
list' Word32
info
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TargetListAddUriTargetsMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.MethodInfo TargetListAddUriTargetsMethodInfo TargetList signature where
    overloadedMethod = targetListAddUriTargets

#endif

-- method TargetList::find
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TargetList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTargetList" , 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 interned atom representing the target to search for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer to the location to store\n       application info for target, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_find" gtk_target_list_find :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    Ptr Gdk.Atom.Atom ->                    -- target : TInterface (Name {namespace = "Gdk", name = "Atom"})
    Ptr Word32 ->                           -- info : TBasicType TUInt
    IO CInt

-- | Looks up a given target in a t'GI.Gtk.Structs.TargetList.TargetList'.
targetListFind ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> Gdk.Atom.Atom
    -- ^ /@target@/: an interned atom representing the target to search for
    -> m ((Bool, Word32))
    -- ^ __Returns:__ 'P.True' if the target was found, otherwise 'P.False'
targetListFind :: TargetList -> Atom -> m (Bool, Word32)
targetListFind list :: TargetList
list target :: Atom
target = IO (Bool, Word32) -> m (Bool, Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Word32) -> m (Bool, Word32))
-> IO (Bool, Word32) -> m (Bool, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    Ptr Atom
target' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
target
    Ptr Word32
info <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    CInt
result <- Ptr TargetList -> Ptr Atom -> Ptr Word32 -> IO CInt
gtk_target_list_find Ptr TargetList
list' Ptr Atom
target' Ptr Word32
info
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Word32
info' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
info
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
target
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
info
    (Bool, Word32) -> IO (Bool, Word32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Word32
info')

#if defined(ENABLE_OVERLOADING)
data TargetListFindMethodInfo
instance (signature ~ (Gdk.Atom.Atom -> m ((Bool, Word32))), MonadIO m) => O.MethodInfo TargetListFindMethodInfo TargetList signature where
    overloadedMethod = targetListFind

#endif

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

foreign import ccall "gtk_target_list_ref" gtk_target_list_ref :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    IO (Ptr TargetList)

-- | Increases the reference count of a t'GI.Gtk.Structs.TargetList.TargetList' by one.
targetListRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> m TargetList
    -- ^ __Returns:__ the passed in t'GI.Gtk.Structs.TargetList.TargetList'.
targetListRef :: TargetList -> m TargetList
targetListRef list :: TargetList
list = IO TargetList -> m TargetList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TargetList -> m TargetList) -> IO TargetList -> m TargetList
forall a b. (a -> b) -> a -> b
$ do
    Ptr TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    Ptr TargetList
result <- Ptr TargetList -> IO (Ptr TargetList)
gtk_target_list_ref Ptr TargetList
list'
    Text -> Ptr TargetList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "targetListRef" Ptr TargetList
result
    TargetList
result' <- ((ManagedPtr TargetList -> TargetList)
-> Ptr TargetList -> IO TargetList
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TargetList -> TargetList
TargetList) Ptr TargetList
result
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    TargetList -> IO TargetList
forall (m :: * -> *) a. Monad m => a -> m a
return TargetList
result'

#if defined(ENABLE_OVERLOADING)
data TargetListRefMethodInfo
instance (signature ~ (m TargetList), MonadIO m) => O.MethodInfo TargetListRefMethodInfo TargetList signature where
    overloadedMethod = targetListRef

#endif

-- method TargetList::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TargetList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTargetList" , 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 "the interned atom representing the target"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_list_remove" gtk_target_list_remove :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    Ptr Gdk.Atom.Atom ->                    -- target : TInterface (Name {namespace = "Gdk", name = "Atom"})
    IO ()

-- | Removes a target from a target list.
targetListRemove ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> Gdk.Atom.Atom
    -- ^ /@target@/: the interned atom representing the target
    -> m ()
targetListRemove :: TargetList -> Atom -> m ()
targetListRemove list :: TargetList
list target :: Atom
target = 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 TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    Ptr Atom
target' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
target
    Ptr TargetList -> Ptr Atom -> IO ()
gtk_target_list_remove Ptr TargetList
list' Ptr Atom
target'
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    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 TargetListRemoveMethodInfo
instance (signature ~ (Gdk.Atom.Atom -> m ()), MonadIO m) => O.MethodInfo TargetListRemoveMethodInfo TargetList signature where
    overloadedMethod = targetListRemove

#endif

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

foreign import ccall "gtk_target_list_unref" gtk_target_list_unref :: 
    Ptr TargetList ->                       -- list : TInterface (Name {namespace = "Gtk", name = "TargetList"})
    IO ()

-- | Decreases the reference count of a t'GI.Gtk.Structs.TargetList.TargetList' by one.
-- If the resulting reference count is zero, frees the list.
targetListUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TargetList
    -- ^ /@list@/: a t'GI.Gtk.Structs.TargetList.TargetList'
    -> m ()
targetListUnref :: TargetList -> m ()
targetListUnref list :: TargetList
list = 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 TargetList
list' <- TargetList -> IO (Ptr TargetList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TargetList
list
    Ptr TargetList -> IO ()
gtk_target_list_unref Ptr TargetList
list'
    TargetList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TargetList
list
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TargetListUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TargetListUnrefMethodInfo TargetList signature where
    overloadedMethod = targetListUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTargetListMethod (t :: Symbol) (o :: *) :: * where
    ResolveTargetListMethod "add" o = TargetListAddMethodInfo
    ResolveTargetListMethod "addImageTargets" o = TargetListAddImageTargetsMethodInfo
    ResolveTargetListMethod "addRichTextTargets" o = TargetListAddRichTextTargetsMethodInfo
    ResolveTargetListMethod "addTable" o = TargetListAddTableMethodInfo
    ResolveTargetListMethod "addTextTargets" o = TargetListAddTextTargetsMethodInfo
    ResolveTargetListMethod "addUriTargets" o = TargetListAddUriTargetsMethodInfo
    ResolveTargetListMethod "find" o = TargetListFindMethodInfo
    ResolveTargetListMethod "ref" o = TargetListRefMethodInfo
    ResolveTargetListMethod "remove" o = TargetListRemoveMethodInfo
    ResolveTargetListMethod "unref" o = TargetListUnrefMethodInfo
    ResolveTargetListMethod l o = O.MethodResolutionFailed l o

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

#endif