{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)

/No description available in the introspection data./
-}

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

module GI.GLib.Structs.TestLogMsg
    (

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


 -- * Methods
-- ** free #method:free#

#if ENABLE_OVERLOADING
    TestLogMsgFreeMethodInfo                ,
#endif
    testLogMsgFree                          ,




 -- * Properties
-- ** logType #attr:logType#
{- | /No description available in the introspection data./
-}
    getTestLogMsgLogType                    ,
    setTestLogMsgLogType                    ,
#if ENABLE_OVERLOADING
    testLogMsg_logType                      ,
#endif


-- ** nNums #attr:nNums#
{- | /No description available in the introspection data./
-}
    getTestLogMsgNNums                      ,
    setTestLogMsgNNums                      ,
#if ENABLE_OVERLOADING
    testLogMsg_nNums                        ,
#endif


-- ** nStrings #attr:nStrings#
{- | /No description available in the introspection data./
-}
    getTestLogMsgNStrings                   ,
    setTestLogMsgNStrings                   ,
#if ENABLE_OVERLOADING
    testLogMsg_nStrings                     ,
#endif


-- ** strings #attr:strings#
{- | /No description available in the introspection data./
-}
    clearTestLogMsgStrings                  ,
    getTestLogMsgStrings                    ,
    setTestLogMsgStrings                    ,
#if 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.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

-- | Memory-managed wrapper type.
newtype TestLogMsg = TestLogMsg (ManagedPtr TestLogMsg)
instance WrappedPtr TestLogMsg where
    wrappedPtrCalloc = callocBytes 32
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 32 >=> wrapPtr TestLogMsg)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `TestLogMsg` struct initialized to zero.
newZeroTestLogMsg :: MonadIO m => m TestLogMsg
newZeroTestLogMsg = liftIO $ wrappedPtrCalloc >>= wrapPtr TestLogMsg

instance tag ~ 'AttrSet => Constructible TestLogMsg tag where
    new _ attrs = do
        o <- newZeroTestLogMsg
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `TestLogMsg`.
noTestLogMsg :: Maybe TestLogMsg
noTestLogMsg = Nothing

{- |
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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

#if ENABLE_OVERLOADING
data TestLogMsgLogTypeFieldInfo
instance AttrInfo TestLogMsgLogTypeFieldInfo where
    type AttrAllowedOps TestLogMsgLogTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestLogMsgLogTypeFieldInfo = (~) GLib.Enums.TestLogType
    type AttrBaseTypeConstraint TestLogMsgLogTypeFieldInfo = (~) TestLogMsg
    type AttrGetType TestLogMsgLogTypeFieldInfo = GLib.Enums.TestLogType
    type AttrLabel TestLogMsgLogTypeFieldInfo = "log_type"
    type AttrOrigin TestLogMsgLogTypeFieldInfo = TestLogMsg
    attrGet _ = getTestLogMsgLogType
    attrSet _ = setTestLogMsgLogType
    attrConstruct = undefined
    attrClear _ = undefined

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO Word32
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 4) (val :: Word32)

#if ENABLE_OVERLOADING
data TestLogMsgNStringsFieldInfo
instance AttrInfo TestLogMsgNStringsFieldInfo where
    type AttrAllowedOps TestLogMsgNStringsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestLogMsgNStringsFieldInfo = (~) Word32
    type AttrBaseTypeConstraint TestLogMsgNStringsFieldInfo = (~) TestLogMsg
    type AttrGetType TestLogMsgNStringsFieldInfo = Word32
    type AttrLabel TestLogMsgNStringsFieldInfo = "n_strings"
    type AttrOrigin TestLogMsgNStringsFieldInfo = TestLogMsg
    attrGet _ = getTestLogMsgNStrings
    attrSet _ = setTestLogMsgNStrings
    attrConstruct = undefined
    attrClear _ = undefined

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data TestLogMsgStringsFieldInfo
instance AttrInfo TestLogMsgStringsFieldInfo where
    type AttrAllowedOps TestLogMsgStringsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TestLogMsgStringsFieldInfo = (~) CString
    type AttrBaseTypeConstraint TestLogMsgStringsFieldInfo = (~) TestLogMsg
    type AttrGetType TestLogMsgStringsFieldInfo = Maybe T.Text
    type AttrLabel TestLogMsgStringsFieldInfo = "strings"
    type AttrOrigin TestLogMsgStringsFieldInfo = TestLogMsg
    attrGet _ = getTestLogMsgStrings
    attrSet _ = setTestLogMsgStrings
    attrConstruct = undefined
    attrClear _ = clearTestLogMsgStrings

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Word32
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Word32)

#if ENABLE_OVERLOADING
data TestLogMsgNNumsFieldInfo
instance AttrInfo TestLogMsgNNumsFieldInfo where
    type AttrAllowedOps TestLogMsgNNumsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestLogMsgNNumsFieldInfo = (~) Word32
    type AttrBaseTypeConstraint TestLogMsgNNumsFieldInfo = (~) TestLogMsg
    type AttrGetType TestLogMsgNNumsFieldInfo = Word32
    type AttrLabel TestLogMsgNNumsFieldInfo = "n_nums"
    type AttrOrigin TestLogMsgNNumsFieldInfo = TestLogMsg
    attrGet _ = getTestLogMsgNNums
    attrSet _ = setTestLogMsgNNums
    attrConstruct = undefined
    attrClear _ = undefined

testLogMsg_nNums :: AttrLabelProxy "nNums"
testLogMsg_nNums = AttrLabelProxy

#endif



#if 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 tmsg = liftIO $ do
    tmsg' <- unsafeManagedPtrGetPtr tmsg
    g_test_log_msg_free tmsg'
    touchManagedPtr tmsg
    return ()

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

#endif

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

#endif