{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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.TestConfig
    ( 

-- * Exported types
    TestConfig(..)                          ,
    newZeroTestConfig                       ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveTestConfigMethod                 ,
#endif



 -- * Properties


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

    getTestConfigTestInitialized            ,
    setTestConfigTestInitialized            ,
#if defined(ENABLE_OVERLOADING)
    testConfig_testInitialized              ,
#endif


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

    getTestConfigTestPerf                   ,
    setTestConfigTestPerf                   ,
#if defined(ENABLE_OVERLOADING)
    testConfig_testPerf                     ,
#endif


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

    getTestConfigTestQuick                  ,
    setTestConfigTestQuick                  ,
#if defined(ENABLE_OVERLOADING)
    testConfig_testQuick                    ,
#endif


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

    getTestConfigTestQuiet                  ,
    setTestConfigTestQuiet                  ,
#if defined(ENABLE_OVERLOADING)
    testConfig_testQuiet                    ,
#endif


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

    getTestConfigTestUndefined              ,
    setTestConfigTestUndefined              ,
#if defined(ENABLE_OVERLOADING)
    testConfig_testUndefined                ,
#endif


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

    getTestConfigTestVerbose                ,
    setTestConfigTestVerbose                ,
#if defined(ENABLE_OVERLOADING)
    testConfig_testVerbose                  ,
#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.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.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


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

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

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


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

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


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

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

#if defined(ENABLE_OVERLOADING)
data TestConfigTestInitializedFieldInfo
instance AttrInfo TestConfigTestInitializedFieldInfo where
    type AttrBaseTypeConstraint TestConfigTestInitializedFieldInfo = (~) TestConfig
    type AttrAllowedOps TestConfigTestInitializedFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestConfigTestInitializedFieldInfo = (~) Bool
    type AttrTransferTypeConstraint TestConfigTestInitializedFieldInfo = (~)Bool
    type AttrTransferType TestConfigTestInitializedFieldInfo = Bool
    type AttrGetType TestConfigTestInitializedFieldInfo = Bool
    type AttrLabel TestConfigTestInitializedFieldInfo = "test_initialized"
    type AttrOrigin TestConfigTestInitializedFieldInfo = TestConfig
    attrGet = getTestConfigTestInitialized
    attrSet = setTestConfigTestInitialized
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

testConfig_testInitialized :: AttrLabelProxy "testInitialized"
testConfig_testInitialized = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data TestConfigTestQuickFieldInfo
instance AttrInfo TestConfigTestQuickFieldInfo where
    type AttrBaseTypeConstraint TestConfigTestQuickFieldInfo = (~) TestConfig
    type AttrAllowedOps TestConfigTestQuickFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestConfigTestQuickFieldInfo = (~) Bool
    type AttrTransferTypeConstraint TestConfigTestQuickFieldInfo = (~)Bool
    type AttrTransferType TestConfigTestQuickFieldInfo = Bool
    type AttrGetType TestConfigTestQuickFieldInfo = Bool
    type AttrLabel TestConfigTestQuickFieldInfo = "test_quick"
    type AttrOrigin TestConfigTestQuickFieldInfo = TestConfig
    attrGet = getTestConfigTestQuick
    attrSet = setTestConfigTestQuick
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

testConfig_testQuick :: AttrLabelProxy "testQuick"
testConfig_testQuick = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data TestConfigTestPerfFieldInfo
instance AttrInfo TestConfigTestPerfFieldInfo where
    type AttrBaseTypeConstraint TestConfigTestPerfFieldInfo = (~) TestConfig
    type AttrAllowedOps TestConfigTestPerfFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestConfigTestPerfFieldInfo = (~) Bool
    type AttrTransferTypeConstraint TestConfigTestPerfFieldInfo = (~)Bool
    type AttrTransferType TestConfigTestPerfFieldInfo = Bool
    type AttrGetType TestConfigTestPerfFieldInfo = Bool
    type AttrLabel TestConfigTestPerfFieldInfo = "test_perf"
    type AttrOrigin TestConfigTestPerfFieldInfo = TestConfig
    attrGet = getTestConfigTestPerf
    attrSet = setTestConfigTestPerf
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

testConfig_testPerf :: AttrLabelProxy "testPerf"
testConfig_testPerf = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data TestConfigTestVerboseFieldInfo
instance AttrInfo TestConfigTestVerboseFieldInfo where
    type AttrBaseTypeConstraint TestConfigTestVerboseFieldInfo = (~) TestConfig
    type AttrAllowedOps TestConfigTestVerboseFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestConfigTestVerboseFieldInfo = (~) Bool
    type AttrTransferTypeConstraint TestConfigTestVerboseFieldInfo = (~)Bool
    type AttrTransferType TestConfigTestVerboseFieldInfo = Bool
    type AttrGetType TestConfigTestVerboseFieldInfo = Bool
    type AttrLabel TestConfigTestVerboseFieldInfo = "test_verbose"
    type AttrOrigin TestConfigTestVerboseFieldInfo = TestConfig
    attrGet = getTestConfigTestVerbose
    attrSet = setTestConfigTestVerbose
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

testConfig_testVerbose :: AttrLabelProxy "testVerbose"
testConfig_testVerbose = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data TestConfigTestQuietFieldInfo
instance AttrInfo TestConfigTestQuietFieldInfo where
    type AttrBaseTypeConstraint TestConfigTestQuietFieldInfo = (~) TestConfig
    type AttrAllowedOps TestConfigTestQuietFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestConfigTestQuietFieldInfo = (~) Bool
    type AttrTransferTypeConstraint TestConfigTestQuietFieldInfo = (~)Bool
    type AttrTransferType TestConfigTestQuietFieldInfo = Bool
    type AttrGetType TestConfigTestQuietFieldInfo = Bool
    type AttrLabel TestConfigTestQuietFieldInfo = "test_quiet"
    type AttrOrigin TestConfigTestQuietFieldInfo = TestConfig
    attrGet = getTestConfigTestQuiet
    attrSet = setTestConfigTestQuiet
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

testConfig_testQuiet :: AttrLabelProxy "testQuiet"
testConfig_testQuiet = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data TestConfigTestUndefinedFieldInfo
instance AttrInfo TestConfigTestUndefinedFieldInfo where
    type AttrBaseTypeConstraint TestConfigTestUndefinedFieldInfo = (~) TestConfig
    type AttrAllowedOps TestConfigTestUndefinedFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TestConfigTestUndefinedFieldInfo = (~) Bool
    type AttrTransferTypeConstraint TestConfigTestUndefinedFieldInfo = (~)Bool
    type AttrTransferType TestConfigTestUndefinedFieldInfo = Bool
    type AttrGetType TestConfigTestUndefinedFieldInfo = Bool
    type AttrLabel TestConfigTestUndefinedFieldInfo = "test_undefined"
    type AttrOrigin TestConfigTestUndefinedFieldInfo = TestConfig
    attrGet = getTestConfigTestUndefined
    attrSet = setTestConfigTestUndefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

testConfig_testUndefined :: AttrLabelProxy "testUndefined"
testConfig_testUndefined = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TestConfig
type instance O.AttributeList TestConfig = TestConfigAttributeList
type TestConfigAttributeList = ('[ '("testInitialized", TestConfigTestInitializedFieldInfo), '("testQuick", TestConfigTestQuickFieldInfo), '("testPerf", TestConfigTestPerfFieldInfo), '("testVerbose", TestConfigTestVerboseFieldInfo), '("testQuiet", TestConfigTestQuietFieldInfo), '("testUndefined", TestConfigTestUndefinedFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTestConfigMethod (t :: Symbol) (o :: *) :: * where
    ResolveTestConfigMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTestConfigMethod t TestConfig, O.OverloadedMethod info TestConfig p) => OL.IsLabel t (TestConfig -> 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 ~ ResolveTestConfigMethod t TestConfig, O.OverloadedMethod info TestConfig p, R.HasField t TestConfig p) => R.HasField t TestConfig p where
    getField = O.overloadedMethod @info

#endif

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

#endif