{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.GLib.Structs.TestConfig
    ( 

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


 -- * Properties
-- ** testInitialized #attr:testInitialized#
    getTestConfigTestInitialized            ,
    setTestConfigTestInitialized            ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    testConfig_testInitialized              ,
#endif


-- ** testPerf #attr:testPerf#
    getTestConfigTestPerf                   ,
    setTestConfigTestPerf                   ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    testConfig_testPerf                     ,
#endif


-- ** testQuick #attr:testQuick#
    getTestConfigTestQuick                  ,
    setTestConfigTestQuick                  ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    testConfig_testQuick                    ,
#endif


-- ** testQuiet #attr:testQuiet#
    getTestConfigTestQuiet                  ,
    setTestConfigTestQuiet                  ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    testConfig_testQuiet                    ,
#endif


-- ** testUndefined #attr:testUndefined#
    getTestConfigTestUndefined              ,
    setTestConfigTestUndefined              ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    testConfig_testUndefined                ,
#endif


-- ** testVerbose #attr:testVerbose#
    getTestConfigTestVerbose                ,
    setTestConfigTestVerbose                ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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


newtype TestConfig = TestConfig (ManagedPtr TestConfig)
instance WrappedPtr TestConfig where
    wrappedPtrCalloc = callocBytes 24
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 24 >=> wrapPtr TestConfig)
    wrappedPtrFree = Just ptr_to_g_free

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

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


noTestConfig :: Maybe TestConfig
noTestConfig = Nothing

getTestConfigTestInitialized :: MonadIO m => TestConfig -> m Bool
getTestConfigTestInitialized s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CInt
    let val' = (/= 0) val
    return val'

setTestConfigTestInitialized :: MonadIO m => TestConfig -> Bool -> m ()
setTestConfigTestInitialized s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CInt)

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

testConfig_testInitialized :: AttrLabelProxy "testInitialized"
testConfig_testInitialized = AttrLabelProxy

#endif


getTestConfigTestQuick :: MonadIO m => TestConfig -> m Bool
getTestConfigTestQuick s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO CInt
    let val' = (/= 0) val
    return val'

setTestConfigTestQuick :: MonadIO m => TestConfig -> Bool -> m ()
setTestConfigTestQuick s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 4) (val' :: CInt)

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

testConfig_testQuick :: AttrLabelProxy "testQuick"
testConfig_testQuick = AttrLabelProxy

#endif


getTestConfigTestPerf :: MonadIO m => TestConfig -> m Bool
getTestConfigTestPerf s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CInt
    let val' = (/= 0) val
    return val'

setTestConfigTestPerf :: MonadIO m => TestConfig -> Bool -> m ()
setTestConfigTestPerf s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 8) (val' :: CInt)

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

testConfig_testPerf :: AttrLabelProxy "testPerf"
testConfig_testPerf = AttrLabelProxy

#endif


getTestConfigTestVerbose :: MonadIO m => TestConfig -> m Bool
getTestConfigTestVerbose s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO CInt
    let val' = (/= 0) val
    return val'

setTestConfigTestVerbose :: MonadIO m => TestConfig -> Bool -> m ()
setTestConfigTestVerbose s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 12) (val' :: CInt)

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

testConfig_testVerbose :: AttrLabelProxy "testVerbose"
testConfig_testVerbose = AttrLabelProxy

#endif


getTestConfigTestQuiet :: MonadIO m => TestConfig -> m Bool
getTestConfigTestQuiet s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CInt
    let val' = (/= 0) val
    return val'

setTestConfigTestQuiet :: MonadIO m => TestConfig -> Bool -> m ()
setTestConfigTestQuiet s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 16) (val' :: CInt)

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

testConfig_testQuiet :: AttrLabelProxy "testQuiet"
testConfig_testQuiet = AttrLabelProxy

#endif


getTestConfigTestUndefined :: MonadIO m => TestConfig -> m Bool
getTestConfigTestUndefined s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: IO CInt
    let val' = (/= 0) val
    return val'

setTestConfigTestUndefined :: MonadIO m => TestConfig -> Bool -> m ()
setTestConfigTestUndefined s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 20) (val' :: CInt)

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

testConfig_testUndefined :: AttrLabelProxy "testUndefined"
testConfig_testUndefined = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
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) && !defined(__HADDOCK_VERSION__)
type family ResolveTestConfigMethod (t :: Symbol) (o :: *) :: * where
    ResolveTestConfigMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTestConfigMethod t TestConfig, O.MethodInfo info TestConfig p) => O.IsLabelProxy t (TestConfig -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveTestConfigMethod t TestConfig, O.MethodInfo info TestConfig p) => O.IsLabel t (TestConfig -> 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

#endif