#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gtk.Structs.TargetEntry
(
TargetEntry(..) ,
newZeroTargetEntry ,
noTargetEntry ,
#if ENABLE_OVERLOADING
TargetEntryCopyMethodInfo ,
#endif
targetEntryCopy ,
#if ENABLE_OVERLOADING
TargetEntryFreeMethodInfo ,
#endif
targetEntryFree ,
targetEntryNew ,
getTargetEntryFlags ,
setTargetEntryFlags ,
#if ENABLE_OVERLOADING
targetEntry_flags ,
#endif
getTargetEntryInfo ,
setTargetEntryInfo ,
#if ENABLE_OVERLOADING
targetEntry_info ,
#endif
clearTargetEntryTarget ,
getTargetEntryTarget ,
setTargetEntryTarget ,
#if ENABLE_OVERLOADING
targetEntry_target ,
#endif
) 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
newtype TargetEntry = TargetEntry (ManagedPtr 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
newZeroTargetEntry :: MonadIO m => m TargetEntry
newZeroTargetEntry = liftIO $ callocBoxedBytes 16 >>= wrapBoxed TargetEntry
instance tag ~ 'AttrSet => Constructible TargetEntry tag where
new _ attrs = do
o <- newZeroTargetEntry
GI.Attributes.set o attrs
return o
noTargetEntry :: Maybe TargetEntry
noTargetEntry = Nothing
getTargetEntryTarget :: MonadIO m => TargetEntry -> m (Maybe T.Text)
getTargetEntryTarget s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CString
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- cstringToText val'
return val''
return result
setTargetEntryTarget :: MonadIO m => TargetEntry -> CString -> m ()
setTargetEntryTarget s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (val :: CString)
clearTargetEntryTarget :: MonadIO m => TargetEntry -> m ()
clearTargetEntryTarget s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)
#if ENABLE_OVERLOADING
data TargetEntryTargetFieldInfo
instance AttrInfo TargetEntryTargetFieldInfo where
type AttrAllowedOps TargetEntryTargetFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TargetEntryTargetFieldInfo = (~) CString
type AttrBaseTypeConstraint TargetEntryTargetFieldInfo = (~) TargetEntry
type AttrGetType TargetEntryTargetFieldInfo = Maybe T.Text
type AttrLabel TargetEntryTargetFieldInfo = "target"
type AttrOrigin TargetEntryTargetFieldInfo = TargetEntry
attrGet _ = getTargetEntryTarget
attrSet _ = setTargetEntryTarget
attrConstruct = undefined
attrClear _ = clearTargetEntryTarget
targetEntry_target :: AttrLabelProxy "target"
targetEntry_target = AttrLabelProxy
#endif
getTargetEntryFlags :: MonadIO m => TargetEntry -> m Word32
getTargetEntryFlags s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO Word32
return val
setTargetEntryFlags :: MonadIO m => TargetEntry -> Word32 -> m ()
setTargetEntryFlags s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Word32)
#if ENABLE_OVERLOADING
data TargetEntryFlagsFieldInfo
instance AttrInfo TargetEntryFlagsFieldInfo where
type AttrAllowedOps TargetEntryFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TargetEntryFlagsFieldInfo = (~) Word32
type AttrBaseTypeConstraint TargetEntryFlagsFieldInfo = (~) TargetEntry
type AttrGetType TargetEntryFlagsFieldInfo = Word32
type AttrLabel TargetEntryFlagsFieldInfo = "flags"
type AttrOrigin TargetEntryFlagsFieldInfo = TargetEntry
attrGet _ = getTargetEntryFlags
attrSet _ = setTargetEntryFlags
attrConstruct = undefined
attrClear _ = undefined
targetEntry_flags :: AttrLabelProxy "flags"
targetEntry_flags = AttrLabelProxy
#endif
getTargetEntryInfo :: MonadIO m => TargetEntry -> m Word32
getTargetEntryInfo s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 12) :: IO Word32
return val
setTargetEntryInfo :: MonadIO m => TargetEntry -> Word32 -> m ()
setTargetEntryInfo s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 12) (val :: Word32)
#if ENABLE_OVERLOADING
data TargetEntryInfoFieldInfo
instance AttrInfo TargetEntryInfoFieldInfo where
type AttrAllowedOps TargetEntryInfoFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TargetEntryInfoFieldInfo = (~) Word32
type AttrBaseTypeConstraint TargetEntryInfoFieldInfo = (~) TargetEntry
type AttrGetType TargetEntryInfoFieldInfo = Word32
type AttrLabel TargetEntryInfoFieldInfo = "info"
type AttrOrigin TargetEntryInfoFieldInfo = TargetEntry
attrGet _ = getTargetEntryInfo
attrSet _ = setTargetEntryInfo
attrConstruct = undefined
attrClear _ = undefined
targetEntry_info :: AttrLabelProxy "info"
targetEntry_info = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList TargetEntry
type instance O.AttributeList TargetEntry = TargetEntryAttributeList
type TargetEntryAttributeList = ('[ '("target", TargetEntryTargetFieldInfo), '("flags", TargetEntryFlagsFieldInfo), '("info", TargetEntryInfoFieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_target_entry_new" gtk_target_entry_new ::
CString ->
Word32 ->
Word32 ->
IO (Ptr TargetEntry)
targetEntryNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Word32
-> Word32
-> m TargetEntry
targetEntryNew target flags info = liftIO $ do
target' <- textToCString target
result <- gtk_target_entry_new target' flags info
checkUnexpectedReturnNULL "targetEntryNew" result
result' <- (wrapBoxed TargetEntry) result
freeMem target'
return result'
#if ENABLE_OVERLOADING
#endif
foreign import ccall "gtk_target_entry_copy" gtk_target_entry_copy ::
Ptr TargetEntry ->
IO (Ptr TargetEntry)
targetEntryCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
TargetEntry
-> m TargetEntry
targetEntryCopy data_ = liftIO $ do
data_' <- unsafeManagedPtrGetPtr data_
result <- gtk_target_entry_copy data_'
checkUnexpectedReturnNULL "targetEntryCopy" result
result' <- (wrapBoxed TargetEntry) result
touchManagedPtr data_
return result'
#if ENABLE_OVERLOADING
data TargetEntryCopyMethodInfo
instance (signature ~ (m TargetEntry), MonadIO m) => O.MethodInfo TargetEntryCopyMethodInfo TargetEntry signature where
overloadedMethod _ = targetEntryCopy
#endif
foreign import ccall "gtk_target_entry_free" gtk_target_entry_free ::
Ptr TargetEntry ->
IO ()
targetEntryFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
TargetEntry
-> m ()
targetEntryFree data_ = liftIO $ do
data_' <- unsafeManagedPtrGetPtr data_
gtk_target_entry_free data_'
touchManagedPtr data_
return ()
#if ENABLE_OVERLOADING
data TargetEntryFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TargetEntryFreeMethodInfo TargetEntry signature where
overloadedMethod _ = targetEntryFree
#endif
#if ENABLE_OVERLOADING
type family ResolveTargetEntryMethod (t :: Symbol) (o :: *) :: * where
ResolveTargetEntryMethod "copy" o = TargetEntryCopyMethodInfo
ResolveTargetEntryMethod "free" o = TargetEntryFreeMethodInfo
ResolveTargetEntryMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTargetEntryMethod t TargetEntry, O.MethodInfo info TargetEntry p) => O.IsLabelProxy t (TargetEntry -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveTargetEntryMethod t TargetEntry, O.MethodInfo info TargetEntry p) => O.IsLabel t (TargetEntry -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif
#endif