{- |
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.TestLogBuffer
    (

-- * Exported types
    TestLogBuffer(..)                       ,
    newZeroTestLogBuffer                    ,
    noTestLogBuffer                         ,


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

#if ENABLE_OVERLOADING
    TestLogBufferFreeMethodInfo             ,
#endif
    testLogBufferFree                       ,


-- ** push #method:push#

#if ENABLE_OVERLOADING
    TestLogBufferPushMethodInfo             ,
#endif
    testLogBufferPush                       ,




    ) 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


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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `TestLogBuffer`.
noTestLogBuffer :: Maybe TestLogBuffer
noTestLogBuffer = Nothing


#if ENABLE_OVERLOADING
instance O.HasAttributeList TestLogBuffer
type instance O.AttributeList TestLogBuffer = TestLogBufferAttributeList
type TestLogBufferAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method TestLogBuffer::free
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "tbuffer", argType = TInterface (Name {namespace = "GLib", name = "TestLogBuffer"}), 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_buffer_free" g_test_log_buffer_free ::
    Ptr TestLogBuffer ->                    -- tbuffer : TInterface (Name {namespace = "GLib", name = "TestLogBuffer"})
    IO ()

{- |
Internal function for gtester to free test log messages, no ABI guarantees provided.
-}
testLogBufferFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TestLogBuffer
    -> m ()
testLogBufferFree tbuffer = liftIO $ do
    tbuffer' <- unsafeManagedPtrGetPtr tbuffer
    g_test_log_buffer_free tbuffer'
    touchManagedPtr tbuffer
    return ()

#if ENABLE_OVERLOADING
data TestLogBufferFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TestLogBufferFreeMethodInfo TestLogBuffer signature where
    overloadedMethod _ = testLogBufferFree

#endif

-- method TestLogBuffer::push
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "tbuffer", argType = TInterface (Name {namespace = "GLib", name = "TestLogBuffer"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "n_bytes", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "bytes", argType = TBasicType TUInt8, 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_buffer_push" g_test_log_buffer_push ::
    Ptr TestLogBuffer ->                    -- tbuffer : TInterface (Name {namespace = "GLib", name = "TestLogBuffer"})
    Word32 ->                               -- n_bytes : TBasicType TUInt
    Word8 ->                                -- bytes : TBasicType TUInt8
    IO ()

{- |
Internal function for gtester to decode test log messages, no ABI guarantees provided.
-}
testLogBufferPush ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TestLogBuffer
    -> Word32
    -> Word8
    -> m ()
testLogBufferPush tbuffer nBytes bytes = liftIO $ do
    tbuffer' <- unsafeManagedPtrGetPtr tbuffer
    g_test_log_buffer_push tbuffer' nBytes bytes
    touchManagedPtr tbuffer
    return ()

#if ENABLE_OVERLOADING
data TestLogBufferPushMethodInfo
instance (signature ~ (Word32 -> Word8 -> m ()), MonadIO m) => O.MethodInfo TestLogBufferPushMethodInfo TestLogBuffer signature where
    overloadedMethod _ = testLogBufferPush

#endif

#if ENABLE_OVERLOADING
type family ResolveTestLogBufferMethod (t :: Symbol) (o :: *) :: * where
    ResolveTestLogBufferMethod "free" o = TestLogBufferFreeMethodInfo
    ResolveTestLogBufferMethod "push" o = TestLogBufferPushMethodInfo
    ResolveTestLogBufferMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTestLogBufferMethod t TestLogBuffer, O.MethodInfo info TestLogBuffer p) => OL.IsLabel t (TestLogBuffer -> 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