{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.GLib.Structs.TestLogMsg
    ( 

-- * Exported types
    TestLogMsg(..)                          ,
    newZeroTestLogMsg                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [free]("GI.GLib.Structs.TestLogMsg#g:method:free").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveTestLogMsgMethod                 ,
#endif

-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    TestLogMsgFreeMethodInfo                ,
#endif
    testLogMsgFree                          ,




 -- * Properties


-- ** logType #attr:logType#
-- | /No description available in the introspection data./

    getTestLogMsgLogType                    ,
    setTestLogMsgLogType                    ,
#if defined(ENABLE_OVERLOADING)
    testLogMsg_logType                      ,
#endif


-- ** nNums #attr:nNums#
-- | /No description available in the introspection data./

    getTestLogMsgNNums                      ,
    setTestLogMsgNNums                      ,
#if defined(ENABLE_OVERLOADING)
    testLogMsg_nNums                        ,
#endif


-- ** nStrings #attr:nStrings#
-- | /No description available in the introspection data./

    getTestLogMsgNStrings                   ,
    setTestLogMsgNStrings                   ,
#if defined(ENABLE_OVERLOADING)
    testLogMsg_nStrings                     ,
#endif


-- ** strings #attr:strings#
-- | /No description available in the introspection data./

    clearTestLogMsgStrings                  ,
    getTestLogMsgStrings                    ,
    setTestLogMsgStrings                    ,
#if defined(ENABLE_OVERLOADING)
    testLogMsg_strings                      ,
#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
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 GHC.Records as R

import {-# SOURCE #-} qualified GI.GLib.Enums as GLib.Enums

-- | Memory-managed wrapper type.
newtype TestLogMsg = TestLogMsg (SP.ManagedPtr TestLogMsg)
    deriving (TestLogMsg -> TestLogMsg -> Bool
(TestLogMsg -> TestLogMsg -> Bool)
-> (TestLogMsg -> TestLogMsg -> Bool) -> Eq TestLogMsg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TestLogMsg -> TestLogMsg -> Bool
== :: TestLogMsg -> TestLogMsg -> Bool
$c/= :: TestLogMsg -> TestLogMsg -> Bool
/= :: TestLogMsg -> TestLogMsg -> Bool
Eq)

instance SP.ManagedPtrNewtype TestLogMsg where
    toManagedPtr :: TestLogMsg -> ManagedPtr TestLogMsg
toManagedPtr (TestLogMsg ManagedPtr TestLogMsg
p) = ManagedPtr TestLogMsg
p

instance BoxedPtr TestLogMsg where
    boxedPtrCopy :: TestLogMsg -> IO TestLogMsg
boxedPtrCopy = \TestLogMsg
p -> TestLogMsg -> (Ptr TestLogMsg -> IO TestLogMsg) -> IO TestLogMsg
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TestLogMsg
p (Int -> Ptr TestLogMsg -> IO (Ptr TestLogMsg)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
32 (Ptr TestLogMsg -> IO (Ptr TestLogMsg))
-> (Ptr TestLogMsg -> IO TestLogMsg)
-> Ptr TestLogMsg
-> IO TestLogMsg
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TestLogMsg -> TestLogMsg)
-> Ptr TestLogMsg -> IO TestLogMsg
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr TestLogMsg -> TestLogMsg
TestLogMsg)
    boxedPtrFree :: TestLogMsg -> IO ()
boxedPtrFree = \TestLogMsg
x -> TestLogMsg -> (Ptr TestLogMsg -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr TestLogMsg
x Ptr TestLogMsg -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr TestLogMsg where
    boxedPtrCalloc :: IO (Ptr TestLogMsg)
boxedPtrCalloc = Int -> IO (Ptr TestLogMsg)
forall a. Int -> IO (Ptr a)
callocBytes Int
32


-- | Construct a `TestLogMsg` struct initialized to zero.
newZeroTestLogMsg :: MonadIO m => m TestLogMsg
newZeroTestLogMsg :: forall (m :: * -> *). MonadIO m => m TestLogMsg
newZeroTestLogMsg = IO TestLogMsg -> m TestLogMsg
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TestLogMsg -> m TestLogMsg) -> IO TestLogMsg -> m TestLogMsg
forall a b. (a -> b) -> a -> b
$ IO (Ptr TestLogMsg)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr TestLogMsg)
-> (Ptr TestLogMsg -> IO TestLogMsg) -> IO TestLogMsg
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TestLogMsg -> TestLogMsg)
-> Ptr TestLogMsg -> IO TestLogMsg
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TestLogMsg -> TestLogMsg
TestLogMsg

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


-- | Get the value of the “@log_type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' testLogMsg #logType
-- @
getTestLogMsgLogType :: MonadIO m => TestLogMsg -> m GLib.Enums.TestLogType
getTestLogMsgLogType :: forall (m :: * -> *). MonadIO m => TestLogMsg -> m TestLogType
getTestLogMsgLogType TestLogMsg
s = IO TestLogType -> m TestLogType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TestLogType -> m TestLogType)
-> IO TestLogType -> m TestLogType
forall a b. (a -> b) -> a -> b
$ TestLogMsg -> (Ptr TestLogMsg -> IO TestLogType) -> IO TestLogType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TestLogMsg
s ((Ptr TestLogMsg -> IO TestLogType) -> IO TestLogType)
-> (Ptr TestLogMsg -> IO TestLogType) -> IO TestLogType
forall a b. (a -> b) -> a -> b
$ \Ptr TestLogMsg
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr TestLogMsg
ptr Ptr TestLogMsg -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CUInt
    let val' :: TestLogType
val' = (Int -> TestLogType
forall a. Enum a => Int -> a
toEnum (Int -> TestLogType) -> (CUInt -> Int) -> CUInt -> TestLogType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    TestLogType -> IO TestLogType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TestLogType
val'

-- | Set the value of the “@log_type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' testLogMsg [ #logType 'Data.GI.Base.Attributes.:=' value ]
-- @
setTestLogMsgLogType :: MonadIO m => TestLogMsg -> GLib.Enums.TestLogType -> m ()
setTestLogMsgLogType :: forall (m :: * -> *).
MonadIO m =>
TestLogMsg -> TestLogType -> m ()
setTestLogMsgLogType TestLogMsg
s TestLogType
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TestLogMsg -> (Ptr TestLogMsg -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TestLogMsg
s ((Ptr TestLogMsg -> IO ()) -> IO ())
-> (Ptr TestLogMsg -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TestLogMsg
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TestLogType -> Int) -> TestLogType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestLogType -> Int
forall a. Enum a => a -> Int
fromEnum) TestLogType
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TestLogMsg
ptr Ptr TestLogMsg -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data TestLogMsgLogTypeFieldInfo
instance AttrInfo TestLogMsgLogTypeFieldInfo where
    type AttrBaseTypeConstraint TestLogMsgLogTypeFieldInfo = (~) TestLogMsg
    type AttrAllowedOps TestLogMsgLogTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestLogMsgLogTypeFieldInfo = (~) GLib.Enums.TestLogType
    type AttrTransferTypeConstraint TestLogMsgLogTypeFieldInfo = (~)GLib.Enums.TestLogType
    type AttrTransferType TestLogMsgLogTypeFieldInfo = GLib.Enums.TestLogType
    type AttrGetType TestLogMsgLogTypeFieldInfo = GLib.Enums.TestLogType
    type AttrLabel TestLogMsgLogTypeFieldInfo = "log_type"
    type AttrOrigin TestLogMsgLogTypeFieldInfo = TestLogMsg
    attrGet = getTestLogMsgLogType
    attrSet = setTestLogMsgLogType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.TestLogMsg.logType"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-TestLogMsg.html#g:attr:logType"
        })

testLogMsg_logType :: AttrLabelProxy "logType"
testLogMsg_logType = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data TestLogMsgNStringsFieldInfo
instance AttrInfo TestLogMsgNStringsFieldInfo where
    type AttrBaseTypeConstraint TestLogMsgNStringsFieldInfo = (~) TestLogMsg
    type AttrAllowedOps TestLogMsgNStringsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestLogMsgNStringsFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TestLogMsgNStringsFieldInfo = (~)Word32
    type AttrTransferType TestLogMsgNStringsFieldInfo = Word32
    type AttrGetType TestLogMsgNStringsFieldInfo = Word32
    type AttrLabel TestLogMsgNStringsFieldInfo = "n_strings"
    type AttrOrigin TestLogMsgNStringsFieldInfo = TestLogMsg
    attrGet = getTestLogMsgNStrings
    attrSet = setTestLogMsgNStrings
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.TestLogMsg.nStrings"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-TestLogMsg.html#g:attr:nStrings"
        })

testLogMsg_nStrings :: AttrLabelProxy "nStrings"
testLogMsg_nStrings = AttrLabelProxy

#endif


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

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

-- | Set the value of the “@strings@” 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' #strings
-- @
clearTestLogMsgStrings :: MonadIO m => TestLogMsg -> m ()
clearTestLogMsgStrings :: forall (m :: * -> *). MonadIO m => TestLogMsg -> m ()
clearTestLogMsgStrings TestLogMsg
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TestLogMsg -> (Ptr TestLogMsg -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TestLogMsg
s ((Ptr TestLogMsg -> IO ()) -> IO ())
-> (Ptr TestLogMsg -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TestLogMsg
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TestLogMsg
ptr Ptr TestLogMsg -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data TestLogMsgStringsFieldInfo
instance AttrInfo TestLogMsgStringsFieldInfo where
    type AttrBaseTypeConstraint TestLogMsgStringsFieldInfo = (~) TestLogMsg
    type AttrAllowedOps TestLogMsgStringsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TestLogMsgStringsFieldInfo = (~) CString
    type AttrTransferTypeConstraint TestLogMsgStringsFieldInfo = (~)CString
    type AttrTransferType TestLogMsgStringsFieldInfo = CString
    type AttrGetType TestLogMsgStringsFieldInfo = Maybe T.Text
    type AttrLabel TestLogMsgStringsFieldInfo = "strings"
    type AttrOrigin TestLogMsgStringsFieldInfo = TestLogMsg
    attrGet = getTestLogMsgStrings
    attrSet = setTestLogMsgStrings
    attrConstruct = undefined
    attrClear = clearTestLogMsgStrings
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.TestLogMsg.strings"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-TestLogMsg.html#g:attr:strings"
        })

testLogMsg_strings :: AttrLabelProxy "strings"
testLogMsg_strings = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data TestLogMsgNNumsFieldInfo
instance AttrInfo TestLogMsgNNumsFieldInfo where
    type AttrBaseTypeConstraint TestLogMsgNNumsFieldInfo = (~) TestLogMsg
    type AttrAllowedOps TestLogMsgNNumsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestLogMsgNNumsFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TestLogMsgNNumsFieldInfo = (~)Word32
    type AttrTransferType TestLogMsgNNumsFieldInfo = Word32
    type AttrGetType TestLogMsgNNumsFieldInfo = Word32
    type AttrLabel TestLogMsgNNumsFieldInfo = "n_nums"
    type AttrOrigin TestLogMsgNNumsFieldInfo = TestLogMsg
    attrGet = getTestLogMsgNNums
    attrSet = setTestLogMsgNNums
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.TestLogMsg.nNums"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-TestLogMsg.html#g:attr:nNums"
        })

testLogMsg_nNums :: AttrLabelProxy "nNums"
testLogMsg_nNums = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TestLogMsg
type instance O.AttributeList TestLogMsg = TestLogMsgAttributeList
type TestLogMsgAttributeList = ('[ '("logType", TestLogMsgLogTypeFieldInfo), '("nStrings", TestLogMsgNStringsFieldInfo), '("strings", TestLogMsgStringsFieldInfo), '("nNums", TestLogMsgNNumsFieldInfo)] :: [(Symbol, *)])
#endif

-- method TestLogMsg::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "tmsg"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "TestLogMsg" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_test_log_msg_free" g_test_log_msg_free :: 
    Ptr TestLogMsg ->                       -- tmsg : TInterface (Name {namespace = "GLib", name = "TestLogMsg"})
    IO ()

-- | Internal function for gtester to free test log messages, no ABI guarantees provided.
testLogMsgFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TestLogMsg
    -> m ()
testLogMsgFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TestLogMsg -> m ()
testLogMsgFree TestLogMsg
tmsg = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr TestLogMsg
tmsg' <- TestLogMsg -> IO (Ptr TestLogMsg)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TestLogMsg
tmsg
    Ptr TestLogMsg -> IO ()
g_test_log_msg_free Ptr TestLogMsg
tmsg'
    TestLogMsg -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TestLogMsg
tmsg
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TestLogMsgFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TestLogMsgFreeMethodInfo TestLogMsg signature where
    overloadedMethod = testLogMsgFree

instance O.OverloadedMethodInfo TestLogMsgFreeMethodInfo TestLogMsg where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.TestLogMsg.testLogMsgFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-TestLogMsg.html#v:testLogMsgFree"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTestLogMsgMethod (t :: Symbol) (o :: *) :: * where
    ResolveTestLogMsgMethod "free" o = TestLogMsgFreeMethodInfo
    ResolveTestLogMsgMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTestLogMsgMethod t TestLogMsg, O.OverloadedMethod info TestLogMsg p, R.HasField t TestLogMsg p) => R.HasField t TestLogMsg p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveTestLogMsgMethod t TestLogMsg, O.OverloadedMethodInfo info TestLogMsg) => OL.IsLabel t (O.MethodProxy info TestLogMsg) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif