{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Associates a string with a bit flag.
-- Used in 'GI.GLib.Functions.parseDebugString'.

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

module GI.GLib.Structs.DebugKey
    ( 

-- * Exported types
    DebugKey(..)                            ,
    newZeroDebugKey                         ,
    noDebugKey                              ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDebugKeyMethod                   ,
#endif




 -- * Properties
-- ** key #attr:key#
-- | the string

    clearDebugKeyKey                        ,
#if defined(ENABLE_OVERLOADING)
    debugKey_key                            ,
#endif
    getDebugKeyKey                          ,
    setDebugKeyKey                          ,


-- ** value #attr:value#
-- | the flag

#if defined(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.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


-- | Memory-managed wrapper type.
newtype DebugKey = DebugKey (ManagedPtr DebugKey)
    deriving (DebugKey -> DebugKey -> Bool
(DebugKey -> DebugKey -> Bool)
-> (DebugKey -> DebugKey -> Bool) -> Eq DebugKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DebugKey -> DebugKey -> Bool
$c/= :: DebugKey -> DebugKey -> Bool
== :: DebugKey -> DebugKey -> Bool
$c== :: DebugKey -> DebugKey -> Bool
Eq)
instance WrappedPtr DebugKey where
    wrappedPtrCalloc :: IO (Ptr DebugKey)
wrappedPtrCalloc = Int -> IO (Ptr DebugKey)
forall a. Int -> IO (Ptr a)
callocBytes 16
    wrappedPtrCopy :: DebugKey -> IO DebugKey
wrappedPtrCopy = \p :: DebugKey
p -> DebugKey -> (Ptr DebugKey -> IO DebugKey) -> IO DebugKey
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DebugKey
p (Int -> Ptr DebugKey -> IO (Ptr DebugKey)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 16 (Ptr DebugKey -> IO (Ptr DebugKey))
-> (Ptr DebugKey -> IO DebugKey) -> Ptr DebugKey -> IO DebugKey
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr DebugKey -> DebugKey) -> Ptr DebugKey -> IO DebugKey
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr DebugKey -> DebugKey
DebugKey)
    wrappedPtrFree :: Maybe (GDestroyNotify DebugKey)
wrappedPtrFree = GDestroyNotify DebugKey -> Maybe (GDestroyNotify DebugKey)
forall a. a -> Maybe a
Just GDestroyNotify DebugKey
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `DebugKey` struct initialized to zero.
newZeroDebugKey :: MonadIO m => m DebugKey
newZeroDebugKey :: m DebugKey
newZeroDebugKey = IO DebugKey -> m DebugKey
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DebugKey -> m DebugKey) -> IO DebugKey -> m DebugKey
forall a b. (a -> b) -> a -> b
$ IO (Ptr DebugKey)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr DebugKey) -> (Ptr DebugKey -> IO DebugKey) -> IO DebugKey
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr DebugKey -> DebugKey) -> Ptr DebugKey -> IO DebugKey
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr DebugKey -> DebugKey
DebugKey

instance tag ~ 'AttrSet => Constructible DebugKey tag where
    new :: (ManagedPtr DebugKey -> DebugKey)
-> [AttrOp DebugKey tag] -> m DebugKey
new _ attrs :: [AttrOp DebugKey tag]
attrs = do
        DebugKey
o <- m DebugKey
forall (m :: * -> *). MonadIO m => m DebugKey
newZeroDebugKey
        DebugKey -> [AttrOp DebugKey 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set DebugKey
o [AttrOp DebugKey tag]
[AttrOp DebugKey 'AttrSet]
attrs
        DebugKey -> m DebugKey
forall (m :: * -> *) a. Monad m => a -> m a
return DebugKey
o


-- | A convenience alias for `Nothing` :: `Maybe` `DebugKey`.
noDebugKey :: Maybe DebugKey
noDebugKey :: Maybe DebugKey
noDebugKey = Maybe DebugKey
forall a. Maybe a
Nothing

-- | Get the value of the “@key@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' debugKey #key
-- @
getDebugKeyKey :: MonadIO m => DebugKey -> m (Maybe T.Text)
getDebugKeyKey :: DebugKey -> m (Maybe Text)
getDebugKeyKey s :: DebugKey
s = 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
$ DebugKey -> (Ptr DebugKey -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DebugKey
s ((Ptr DebugKey -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr DebugKey -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DebugKey
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr DebugKey
ptr Ptr DebugKey -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \val' :: CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@key@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' debugKey [ #key 'Data.GI.Base.Attributes.:=' value ]
-- @
setDebugKeyKey :: MonadIO m => DebugKey -> CString -> m ()
setDebugKeyKey :: DebugKey -> CString -> m ()
setDebugKeyKey s :: DebugKey
s val :: CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DebugKey -> (Ptr DebugKey -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DebugKey
s ((Ptr DebugKey -> IO ()) -> IO ())
-> (Ptr DebugKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DebugKey
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DebugKey
ptr Ptr DebugKey -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CString
val :: CString)

-- | Set the value of the “@key@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #key
-- @
clearDebugKeyKey :: MonadIO m => DebugKey -> m ()
clearDebugKeyKey :: DebugKey -> m ()
clearDebugKeyKey s :: DebugKey
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DebugKey -> (Ptr DebugKey -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DebugKey
s ((Ptr DebugKey -> IO ()) -> IO ())
-> (Ptr DebugKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DebugKey
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DebugKey
ptr Ptr DebugKey -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data DebugKeyKeyFieldInfo
instance AttrInfo DebugKeyKeyFieldInfo where
    type AttrBaseTypeConstraint DebugKeyKeyFieldInfo = (~) DebugKey
    type AttrAllowedOps DebugKeyKeyFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DebugKeyKeyFieldInfo = (~) CString
    type AttrTransferTypeConstraint DebugKeyKeyFieldInfo = (~)CString
    type AttrTransferType DebugKeyKeyFieldInfo = CString
    type AttrGetType DebugKeyKeyFieldInfo = Maybe T.Text
    type AttrLabel DebugKeyKeyFieldInfo = "key"
    type AttrOrigin DebugKeyKeyFieldInfo = DebugKey
    attrGet = getDebugKeyKey
    attrSet = setDebugKeyKey
    attrConstruct = undefined
    attrClear = clearDebugKeyKey
    attrTransfer _ v = do
        return v

debugKey_key :: AttrLabelProxy "key"
debugKey_key = AttrLabelProxy

#endif


-- | Get the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' debugKey #value
-- @
getDebugKeyValue :: MonadIO m => DebugKey -> m Word32
getDebugKeyValue :: DebugKey -> m Word32
getDebugKeyValue s :: DebugKey
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ DebugKey -> (Ptr DebugKey -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DebugKey
s ((Ptr DebugKey -> IO Word32) -> IO Word32)
-> (Ptr DebugKey -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DebugKey
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr DebugKey
ptr Ptr DebugKey -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' debugKey [ #value 'Data.GI.Base.Attributes.:=' value ]
-- @
setDebugKeyValue :: MonadIO m => DebugKey -> Word32 -> m ()
setDebugKeyValue :: DebugKey -> Word32 -> m ()
setDebugKeyValue s :: DebugKey
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DebugKey -> (Ptr DebugKey -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DebugKey
s ((Ptr DebugKey -> IO ()) -> IO ())
-> (Ptr DebugKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr DebugKey
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DebugKey
ptr Ptr DebugKey -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data DebugKeyValueFieldInfo
instance AttrInfo DebugKeyValueFieldInfo where
    type AttrBaseTypeConstraint DebugKeyValueFieldInfo = (~) DebugKey
    type AttrAllowedOps DebugKeyValueFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DebugKeyValueFieldInfo = (~) Word32
    type AttrTransferTypeConstraint DebugKeyValueFieldInfo = (~)Word32
    type AttrTransferType DebugKeyValueFieldInfo = Word32
    type AttrGetType DebugKeyValueFieldInfo = Word32
    type AttrLabel DebugKeyValueFieldInfo = "value"
    type AttrOrigin DebugKeyValueFieldInfo = DebugKey
    attrGet = getDebugKeyValue
    attrSet = setDebugKeyValue
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

debugKey_value :: AttrLabelProxy "value"
debugKey_value = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DebugKey
type instance O.AttributeList DebugKey = DebugKeyAttributeList
type DebugKeyAttributeList = ('[ '("key", DebugKeyKeyFieldInfo), '("value", DebugKeyValueFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(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 @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif