{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Structs.TestLogMsg
(
TestLogMsg(..) ,
newZeroTestLogMsg ,
noTestLogMsg ,
#if defined(ENABLE_OVERLOADING)
ResolveTestLogMsgMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TestLogMsgFreeMethodInfo ,
#endif
testLogMsgFree ,
getTestLogMsgLogType ,
setTestLogMsgLogType ,
#if defined(ENABLE_OVERLOADING)
testLogMsg_logType ,
#endif
getTestLogMsgNNums ,
setTestLogMsgNNums ,
#if defined(ENABLE_OVERLOADING)
testLogMsg_nNums ,
#endif
getTestLogMsgNStrings ,
setTestLogMsgNStrings ,
#if defined(ENABLE_OVERLOADING)
testLogMsg_nStrings ,
#endif
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.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
import {-# SOURCE #-} qualified GI.GLib.Enums as GLib.Enums
newtype TestLogMsg = TestLogMsg (ManagedPtr TestLogMsg)
deriving (TestLogMsg -> TestLogMsg -> Bool
(TestLogMsg -> TestLogMsg -> Bool)
-> (TestLogMsg -> TestLogMsg -> Bool) -> Eq TestLogMsg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestLogMsg -> TestLogMsg -> Bool
$c/= :: TestLogMsg -> TestLogMsg -> Bool
== :: TestLogMsg -> TestLogMsg -> Bool
$c== :: TestLogMsg -> TestLogMsg -> Bool
Eq)
instance WrappedPtr TestLogMsg where
wrappedPtrCalloc :: IO (Ptr TestLogMsg)
wrappedPtrCalloc = Int -> IO (Ptr TestLogMsg)
forall a. Int -> IO (Ptr a)
callocBytes 32
wrappedPtrCopy :: TestLogMsg -> IO TestLogMsg
wrappedPtrCopy = \p :: TestLogMsg
p -> TestLogMsg -> (Ptr TestLogMsg -> IO TestLogMsg) -> IO TestLogMsg
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TestLogMsg
p (Int -> Ptr TestLogMsg -> IO (Ptr TestLogMsg)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 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, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TestLogMsg -> TestLogMsg
TestLogMsg)
wrappedPtrFree :: Maybe (GDestroyNotify TestLogMsg)
wrappedPtrFree = GDestroyNotify TestLogMsg -> Maybe (GDestroyNotify TestLogMsg)
forall a. a -> Maybe a
Just GDestroyNotify TestLogMsg
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroTestLogMsg :: MonadIO m => m TestLogMsg
newZeroTestLogMsg :: m TestLogMsg
newZeroTestLogMsg = IO TestLogMsg -> m TestLogMsg
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. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr TestLogMsg)
-> (Ptr TestLogMsg -> IO TestLogMsg) -> IO TestLogMsg
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TestLogMsg -> TestLogMsg)
-> Ptr TestLogMsg -> IO TestLogMsg
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TestLogMsg -> TestLogMsg
TestLogMsg
instance tag ~ 'AttrSet => Constructible TestLogMsg tag where
new :: (ManagedPtr TestLogMsg -> TestLogMsg)
-> [AttrOp TestLogMsg tag] -> m TestLogMsg
new _ attrs :: [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 (m :: * -> *) a. Monad m => a -> m a
return TestLogMsg
o
noTestLogMsg :: Maybe TestLogMsg
noTestLogMsg :: Maybe TestLogMsg
noTestLogMsg = Maybe TestLogMsg
forall a. Maybe a
Nothing
getTestLogMsgLogType :: MonadIO m => TestLogMsg -> m GLib.Enums.TestLogType
getTestLogMsgLogType :: TestLogMsg -> m TestLogType
getTestLogMsgLogType s :: TestLogMsg
s = IO TestLogType -> m TestLogType
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 :: 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` 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 (m :: * -> *) a. Monad m => a -> m a
return TestLogType
val'
setTestLogMsgLogType :: MonadIO m => TestLogMsg -> GLib.Enums.TestLogType -> m ()
setTestLogMsgLogType :: TestLogMsg -> TestLogType -> m ()
setTestLogMsgLogType s :: TestLogMsg
s val :: TestLogType
val = IO () -> m ()
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 :: 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` 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
testLogMsg_logType :: AttrLabelProxy "logType"
testLogMsg_logType = AttrLabelProxy
#endif
getTestLogMsgNStrings :: MonadIO m => TestLogMsg -> m Word32
getTestLogMsgNStrings :: TestLogMsg -> m Word32
getTestLogMsgNStrings s :: TestLogMsg
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
$ 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 :: 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` 4) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTestLogMsgNStrings :: MonadIO m => TestLogMsg -> Word32 -> m ()
setTestLogMsgNStrings :: TestLogMsg -> Word32 -> m ()
setTestLogMsgNStrings s :: TestLogMsg
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
$ 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 :: 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` 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
testLogMsg_nStrings :: AttrLabelProxy "nStrings"
testLogMsg_nStrings = AttrLabelProxy
#endif
getTestLogMsgStrings :: MonadIO m => TestLogMsg -> m (Maybe T.Text)
getTestLogMsgStrings :: TestLogMsg -> m (Maybe Text)
getTestLogMsgStrings s :: TestLogMsg
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
$ 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 :: 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` 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
$ \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
setTestLogMsgStrings :: MonadIO m => TestLogMsg -> CString -> m ()
setTestLogMsgStrings :: TestLogMsg -> CString -> m ()
setTestLogMsgStrings s :: TestLogMsg
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
$ 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 :: 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` 8) (CString
val :: CString)
clearTestLogMsgStrings :: MonadIO m => TestLogMsg -> m ()
clearTestLogMsgStrings :: TestLogMsg -> m ()
clearTestLogMsgStrings s :: TestLogMsg
s = IO () -> m ()
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 :: 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` 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
testLogMsg_strings :: AttrLabelProxy "strings"
testLogMsg_strings = AttrLabelProxy
#endif
getTestLogMsgNNums :: MonadIO m => TestLogMsg -> m Word32
getTestLogMsgNNums :: TestLogMsg -> m Word32
getTestLogMsgNNums s :: TestLogMsg
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
$ 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 :: 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` 16) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTestLogMsgNNums :: MonadIO m => TestLogMsg -> Word32 -> m ()
setTestLogMsgNNums :: TestLogMsg -> Word32 -> m ()
setTestLogMsgNNums s :: TestLogMsg
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
$ 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 :: 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` 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
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
foreign import ccall "g_test_log_msg_free" g_test_log_msg_free ::
Ptr TestLogMsg ->
IO ()
testLogMsgFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
TestLogMsg
-> m ()
testLogMsgFree :: TestLogMsg -> m ()
testLogMsgFree tmsg :: TestLogMsg
tmsg = IO () -> m ()
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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TestLogMsgFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TestLogMsgFreeMethodInfo TestLogMsg signature where
overloadedMethod = 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.MethodInfo 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
#endif