{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

A #GtkTargetEntry represents a single type of
data than can be supplied for by a widget for a selection
or for supplied or received during drag-and-drop.
-}

module GI.Gtk.Structs.TargetEntry
    ( 

-- * Exported types
    TargetEntry(..)                         ,
    noTargetEntry                           ,


 -- * Methods
-- ** targetEntryCopy
    targetEntryCopy                         ,


-- ** targetEntryFree
    targetEntryFree                         ,


-- ** targetEntryNew
    targetEntryNew                          ,




 -- * Properties
-- ** Flags
    targetEntryReadFlags                    ,


-- ** Info
    targetEntryReadInfo                     ,


-- ** Target
    targetEntryReadTarget                   ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gtk.Types
import GI.Gtk.Callbacks

newtype TargetEntry = TargetEntry (ForeignPtr TargetEntry)
foreign import ccall "gtk_target_entry_get_type" c_gtk_target_entry_get_type :: 
    IO GType

instance BoxedObject TargetEntry where
    boxedType _ = c_gtk_target_entry_get_type

noTargetEntry :: Maybe TargetEntry
noTargetEntry = Nothing

targetEntryReadTarget :: TargetEntry -> IO T.Text
targetEntryReadTarget s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CString
    val' <- cstringToText val
    return val'

targetEntryReadFlags :: TargetEntry -> IO Word32
targetEntryReadFlags s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Word32
    return val

targetEntryReadInfo :: TargetEntry -> IO Word32
targetEntryReadInfo s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO Word32
    return val

-- method TargetEntry::new
-- method type : Constructor
-- Args : [Arg {argName = "target", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "info", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "target", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "info", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "TargetEntry"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_entry_new" gtk_target_entry_new :: 
    CString ->                              -- target : TBasicType TUTF8
    Word32 ->                               -- flags : TBasicType TUInt32
    Word32 ->                               -- info : TBasicType TUInt32
    IO (Ptr TargetEntry)


targetEntryNew ::
    (MonadIO m) =>
    T.Text ->                               -- target
    Word32 ->                               -- flags
    Word32 ->                               -- info
    m TargetEntry
targetEntryNew target flags info = liftIO $ do
    target' <- textToCString target
    result <- gtk_target_entry_new target' flags info
    checkUnexpectedReturnNULL "gtk_target_entry_new" result
    result' <- (wrapBoxed TargetEntry) result
    freeMem target'
    return result'

-- method TargetEntry::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TargetEntry", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TargetEntry", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gtk" "TargetEntry"
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_entry_copy" gtk_target_entry_copy :: 
    Ptr TargetEntry ->                      -- _obj : TInterface "Gtk" "TargetEntry"
    IO (Ptr TargetEntry)


targetEntryCopy ::
    (MonadIO m) =>
    TargetEntry ->                          -- _obj
    m TargetEntry
targetEntryCopy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- gtk_target_entry_copy _obj'
    checkUnexpectedReturnNULL "gtk_target_entry_copy" result
    result' <- (wrapBoxed TargetEntry) result
    touchManagedPtr _obj
    return result'

-- method TargetEntry::free
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gtk" "TargetEntry", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gtk" "TargetEntry", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "gtk_target_entry_free" gtk_target_entry_free :: 
    Ptr TargetEntry ->                      -- _obj : TInterface "Gtk" "TargetEntry"
    IO ()


targetEntryFree ::
    (MonadIO m) =>
    TargetEntry ->                          -- _obj
    m ()
targetEntryFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    gtk_target_entry_free _obj'
    touchManagedPtr _obj
    return ()