#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.GLib.Structs.DebugKey
(
DebugKey(..) ,
newZeroDebugKey ,
noDebugKey ,
clearDebugKeyKey ,
#if ENABLE_OVERLOADING
debugKey_key ,
#endif
getDebugKeyKey ,
setDebugKeyKey ,
#if ENABLE_OVERLOADING
debugKey_value ,
#endif
getDebugKeyValue ,
setDebugKeyValue ,
) 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.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
newtype DebugKey = DebugKey (ManagedPtr DebugKey)
instance WrappedPtr DebugKey where
wrappedPtrCalloc = callocBytes 16
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 16 >=> wrapPtr DebugKey)
wrappedPtrFree = Just ptr_to_g_free
newZeroDebugKey :: MonadIO m => m DebugKey
newZeroDebugKey = liftIO $ wrappedPtrCalloc >>= wrapPtr DebugKey
instance tag ~ 'AttrSet => Constructible DebugKey tag where
new _ attrs = do
o <- newZeroDebugKey
GI.Attributes.set o attrs
return o
noDebugKey :: Maybe DebugKey
noDebugKey = Nothing
getDebugKeyKey :: MonadIO m => DebugKey -> m (Maybe T.Text)
getDebugKeyKey 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
setDebugKeyKey :: MonadIO m => DebugKey -> CString -> m ()
setDebugKeyKey s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (val :: CString)
clearDebugKeyKey :: MonadIO m => DebugKey -> m ()
clearDebugKeyKey s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)
#if ENABLE_OVERLOADING
data DebugKeyKeyFieldInfo
instance AttrInfo DebugKeyKeyFieldInfo where
type AttrAllowedOps DebugKeyKeyFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint DebugKeyKeyFieldInfo = (~) CString
type AttrBaseTypeConstraint DebugKeyKeyFieldInfo = (~) DebugKey
type AttrGetType DebugKeyKeyFieldInfo = Maybe T.Text
type AttrLabel DebugKeyKeyFieldInfo = "key"
type AttrOrigin DebugKeyKeyFieldInfo = DebugKey
attrGet _ = getDebugKeyKey
attrSet _ = setDebugKeyKey
attrConstruct = undefined
attrClear _ = clearDebugKeyKey
debugKey_key :: AttrLabelProxy "key"
debugKey_key = AttrLabelProxy
#endif
getDebugKeyValue :: MonadIO m => DebugKey -> m Word32
getDebugKeyValue s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO Word32
return val
setDebugKeyValue :: MonadIO m => DebugKey -> Word32 -> m ()
setDebugKeyValue s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Word32)
#if ENABLE_OVERLOADING
data DebugKeyValueFieldInfo
instance AttrInfo DebugKeyValueFieldInfo where
type AttrAllowedOps DebugKeyValueFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint DebugKeyValueFieldInfo = (~) Word32
type AttrBaseTypeConstraint DebugKeyValueFieldInfo = (~) DebugKey
type AttrGetType DebugKeyValueFieldInfo = Word32
type AttrLabel DebugKeyValueFieldInfo = "value"
type AttrOrigin DebugKeyValueFieldInfo = DebugKey
attrGet _ = getDebugKeyValue
attrSet _ = setDebugKeyValue
attrConstruct = undefined
attrClear _ = undefined
debugKey_value :: AttrLabelProxy "value"
debugKey_value = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList DebugKey
type instance O.AttributeList DebugKey = DebugKeyAttributeList
type DebugKeyAttributeList = ('[ '("key", DebugKeyKeyFieldInfo), '("value", DebugKeyValueFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveDebugKeyMethod (t :: Symbol) (o :: *) :: * where
ResolveDebugKeyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDebugKeyMethod t DebugKey, O.MethodInfo info DebugKey p) => OL.IsLabel t (DebugKey -> 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