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

A union holding the value of the token.
-}

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

module GI.GLib.Unions.TokenValue
    (

-- * Exported types
    TokenValue(..)                          ,
    newZeroTokenValue                       ,
    noTokenValue                            ,


 -- * Properties
-- ** vBinary #attr:vBinary#
{- | token binary integer value
-}
    getTokenValueVBinary                    ,
    setTokenValueVBinary                    ,
#if ENABLE_OVERLOADING
    tokenValue_vBinary                      ,
#endif


-- ** vChar #attr:vChar#
{- | character value
-}
    getTokenValueVChar                      ,
    setTokenValueVChar                      ,
#if ENABLE_OVERLOADING
    tokenValue_vChar                        ,
#endif


-- ** vComment #attr:vComment#
{- | comment value
-}
    clearTokenValueVComment                 ,
    getTokenValueVComment                   ,
    setTokenValueVComment                   ,
#if ENABLE_OVERLOADING
    tokenValue_vComment                     ,
#endif


-- ** vError #attr:vError#
{- | error value
-}
    getTokenValueVError                     ,
    setTokenValueVError                     ,
#if ENABLE_OVERLOADING
    tokenValue_vError                       ,
#endif


-- ** vFloat #attr:vFloat#
{- | floating point value
-}
    getTokenValueVFloat                     ,
    setTokenValueVFloat                     ,
#if ENABLE_OVERLOADING
    tokenValue_vFloat                       ,
#endif


-- ** vHex #attr:vHex#
{- | hex integer value
-}
    getTokenValueVHex                       ,
    setTokenValueVHex                       ,
#if ENABLE_OVERLOADING
    tokenValue_vHex                         ,
#endif


-- ** vIdentifier #attr:vIdentifier#
{- | token identifier value
-}
    clearTokenValueVIdentifier              ,
    getTokenValueVIdentifier                ,
    setTokenValueVIdentifier                ,
#if ENABLE_OVERLOADING
    tokenValue_vIdentifier                  ,
#endif


-- ** vInt #attr:vInt#
{- | integer value
-}
    getTokenValueVInt                       ,
    setTokenValueVInt                       ,
#if ENABLE_OVERLOADING
    tokenValue_vInt                         ,
#endif


-- ** vInt64 #attr:vInt64#
{- | 64-bit integer value
-}
    getTokenValueVInt64                     ,
    setTokenValueVInt64                     ,
#if ENABLE_OVERLOADING
    tokenValue_vInt64                       ,
#endif


-- ** vOctal #attr:vOctal#
{- | octal integer value
-}
    getTokenValueVOctal                     ,
    setTokenValueVOctal                     ,
#if ENABLE_OVERLOADING
    tokenValue_vOctal                       ,
#endif


-- ** vString #attr:vString#
{- | string value
-}
    clearTokenValueVString                  ,
    getTokenValueVString                    ,
    setTokenValueVString                    ,
#if ENABLE_OVERLOADING
    tokenValue_vString                      ,
#endif


-- ** vSymbol #attr:vSymbol#
{- | token symbol value
-}
    clearTokenValueVSymbol                  ,
    getTokenValueVSymbol                    ,
    setTokenValueVSymbol                    ,
#if ENABLE_OVERLOADING
    tokenValue_vSymbol                      ,
#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


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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `TokenValue`.
noTokenValue :: Maybe TokenValue
noTokenValue = Nothing

{- |
Get the value of the “@v_symbol@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vSymbol
@
-}
getTokenValueVSymbol :: MonadIO m => TokenValue -> m (Ptr ())
getTokenValueVSymbol s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr ())
    return val

{- |
Set the value of the “@v_symbol@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vSymbol 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVSymbol :: MonadIO m => TokenValue -> Ptr () -> m ()
setTokenValueVSymbol s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Ptr ())

{- |
Set the value of the “@v_symbol@” 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' #vSymbol
@
-}
clearTokenValueVSymbol :: MonadIO m => TokenValue -> m ()
clearTokenValueVSymbol s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: Ptr ())

#if ENABLE_OVERLOADING
data TokenValueVSymbolFieldInfo
instance AttrInfo TokenValueVSymbolFieldInfo where
    type AttrAllowedOps TokenValueVSymbolFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TokenValueVSymbolFieldInfo = (~) (Ptr ())
    type AttrBaseTypeConstraint TokenValueVSymbolFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVSymbolFieldInfo = Ptr ()
    type AttrLabel TokenValueVSymbolFieldInfo = "v_symbol"
    type AttrOrigin TokenValueVSymbolFieldInfo = TokenValue
    attrGet _ = getTokenValueVSymbol
    attrSet _ = setTokenValueVSymbol
    attrConstruct = undefined
    attrClear _ = clearTokenValueVSymbol

tokenValue_vSymbol :: AttrLabelProxy "vSymbol"
tokenValue_vSymbol = AttrLabelProxy

#endif


{- |
Get the value of the “@v_identifier@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vIdentifier
@
-}
getTokenValueVIdentifier :: MonadIO m => TokenValue -> m (Maybe T.Text)
getTokenValueVIdentifier s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

{- |
Set the value of the “@v_identifier@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vIdentifier 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVIdentifier :: MonadIO m => TokenValue -> CString -> m ()
setTokenValueVIdentifier s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CString)

{- |
Set the value of the “@v_identifier@” 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' #vIdentifier
@
-}
clearTokenValueVIdentifier :: MonadIO m => TokenValue -> m ()
clearTokenValueVIdentifier s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data TokenValueVIdentifierFieldInfo
instance AttrInfo TokenValueVIdentifierFieldInfo where
    type AttrAllowedOps TokenValueVIdentifierFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TokenValueVIdentifierFieldInfo = (~) CString
    type AttrBaseTypeConstraint TokenValueVIdentifierFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVIdentifierFieldInfo = Maybe T.Text
    type AttrLabel TokenValueVIdentifierFieldInfo = "v_identifier"
    type AttrOrigin TokenValueVIdentifierFieldInfo = TokenValue
    attrGet _ = getTokenValueVIdentifier
    attrSet _ = setTokenValueVIdentifier
    attrConstruct = undefined
    attrClear _ = clearTokenValueVIdentifier

tokenValue_vIdentifier :: AttrLabelProxy "vIdentifier"
tokenValue_vIdentifier = AttrLabelProxy

#endif


{- |
Get the value of the “@v_binary@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vBinary
@
-}
getTokenValueVBinary :: MonadIO m => TokenValue -> m CULong
getTokenValueVBinary s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CULong
    return val

{- |
Set the value of the “@v_binary@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vBinary 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVBinary :: MonadIO m => TokenValue -> CULong -> m ()
setTokenValueVBinary s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CULong)

#if ENABLE_OVERLOADING
data TokenValueVBinaryFieldInfo
instance AttrInfo TokenValueVBinaryFieldInfo where
    type AttrAllowedOps TokenValueVBinaryFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TokenValueVBinaryFieldInfo = (~) CULong
    type AttrBaseTypeConstraint TokenValueVBinaryFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVBinaryFieldInfo = CULong
    type AttrLabel TokenValueVBinaryFieldInfo = "v_binary"
    type AttrOrigin TokenValueVBinaryFieldInfo = TokenValue
    attrGet _ = getTokenValueVBinary
    attrSet _ = setTokenValueVBinary
    attrConstruct = undefined
    attrClear _ = undefined

tokenValue_vBinary :: AttrLabelProxy "vBinary"
tokenValue_vBinary = AttrLabelProxy

#endif


{- |
Get the value of the “@v_octal@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vOctal
@
-}
getTokenValueVOctal :: MonadIO m => TokenValue -> m CULong
getTokenValueVOctal s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CULong
    return val

{- |
Set the value of the “@v_octal@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vOctal 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVOctal :: MonadIO m => TokenValue -> CULong -> m ()
setTokenValueVOctal s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CULong)

#if ENABLE_OVERLOADING
data TokenValueVOctalFieldInfo
instance AttrInfo TokenValueVOctalFieldInfo where
    type AttrAllowedOps TokenValueVOctalFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TokenValueVOctalFieldInfo = (~) CULong
    type AttrBaseTypeConstraint TokenValueVOctalFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVOctalFieldInfo = CULong
    type AttrLabel TokenValueVOctalFieldInfo = "v_octal"
    type AttrOrigin TokenValueVOctalFieldInfo = TokenValue
    attrGet _ = getTokenValueVOctal
    attrSet _ = setTokenValueVOctal
    attrConstruct = undefined
    attrClear _ = undefined

tokenValue_vOctal :: AttrLabelProxy "vOctal"
tokenValue_vOctal = AttrLabelProxy

#endif


{- |
Get the value of the “@v_int@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vInt
@
-}
getTokenValueVInt :: MonadIO m => TokenValue -> m CULong
getTokenValueVInt s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CULong
    return val

{- |
Set the value of the “@v_int@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vInt 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVInt :: MonadIO m => TokenValue -> CULong -> m ()
setTokenValueVInt s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CULong)

#if ENABLE_OVERLOADING
data TokenValueVIntFieldInfo
instance AttrInfo TokenValueVIntFieldInfo where
    type AttrAllowedOps TokenValueVIntFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TokenValueVIntFieldInfo = (~) CULong
    type AttrBaseTypeConstraint TokenValueVIntFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVIntFieldInfo = CULong
    type AttrLabel TokenValueVIntFieldInfo = "v_int"
    type AttrOrigin TokenValueVIntFieldInfo = TokenValue
    attrGet _ = getTokenValueVInt
    attrSet _ = setTokenValueVInt
    attrConstruct = undefined
    attrClear _ = undefined

tokenValue_vInt :: AttrLabelProxy "vInt"
tokenValue_vInt = AttrLabelProxy

#endif


{- |
Get the value of the “@v_int64@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vInt64
@
-}
getTokenValueVInt64 :: MonadIO m => TokenValue -> m Word64
getTokenValueVInt64 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Word64
    return val

{- |
Set the value of the “@v_int64@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vInt64 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVInt64 :: MonadIO m => TokenValue -> Word64 -> m ()
setTokenValueVInt64 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Word64)

#if ENABLE_OVERLOADING
data TokenValueVInt64FieldInfo
instance AttrInfo TokenValueVInt64FieldInfo where
    type AttrAllowedOps TokenValueVInt64FieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TokenValueVInt64FieldInfo = (~) Word64
    type AttrBaseTypeConstraint TokenValueVInt64FieldInfo = (~) TokenValue
    type AttrGetType TokenValueVInt64FieldInfo = Word64
    type AttrLabel TokenValueVInt64FieldInfo = "v_int64"
    type AttrOrigin TokenValueVInt64FieldInfo = TokenValue
    attrGet _ = getTokenValueVInt64
    attrSet _ = setTokenValueVInt64
    attrConstruct = undefined
    attrClear _ = undefined

tokenValue_vInt64 :: AttrLabelProxy "vInt64"
tokenValue_vInt64 = AttrLabelProxy

#endif


{- |
Get the value of the “@v_float@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vFloat
@
-}
getTokenValueVFloat :: MonadIO m => TokenValue -> m Double
getTokenValueVFloat s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CDouble
    let val' = realToFrac val
    return val'

{- |
Set the value of the “@v_float@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vFloat 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVFloat :: MonadIO m => TokenValue -> Double -> m ()
setTokenValueVFloat s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 0) (val' :: CDouble)

#if ENABLE_OVERLOADING
data TokenValueVFloatFieldInfo
instance AttrInfo TokenValueVFloatFieldInfo where
    type AttrAllowedOps TokenValueVFloatFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TokenValueVFloatFieldInfo = (~) Double
    type AttrBaseTypeConstraint TokenValueVFloatFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVFloatFieldInfo = Double
    type AttrLabel TokenValueVFloatFieldInfo = "v_float"
    type AttrOrigin TokenValueVFloatFieldInfo = TokenValue
    attrGet _ = getTokenValueVFloat
    attrSet _ = setTokenValueVFloat
    attrConstruct = undefined
    attrClear _ = undefined

tokenValue_vFloat :: AttrLabelProxy "vFloat"
tokenValue_vFloat = AttrLabelProxy

#endif


{- |
Get the value of the “@v_hex@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vHex
@
-}
getTokenValueVHex :: MonadIO m => TokenValue -> m CULong
getTokenValueVHex s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CULong
    return val

{- |
Set the value of the “@v_hex@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vHex 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVHex :: MonadIO m => TokenValue -> CULong -> m ()
setTokenValueVHex s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CULong)

#if ENABLE_OVERLOADING
data TokenValueVHexFieldInfo
instance AttrInfo TokenValueVHexFieldInfo where
    type AttrAllowedOps TokenValueVHexFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TokenValueVHexFieldInfo = (~) CULong
    type AttrBaseTypeConstraint TokenValueVHexFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVHexFieldInfo = CULong
    type AttrLabel TokenValueVHexFieldInfo = "v_hex"
    type AttrOrigin TokenValueVHexFieldInfo = TokenValue
    attrGet _ = getTokenValueVHex
    attrSet _ = setTokenValueVHex
    attrConstruct = undefined
    attrClear _ = undefined

tokenValue_vHex :: AttrLabelProxy "vHex"
tokenValue_vHex = AttrLabelProxy

#endif


{- |
Get the value of the “@v_string@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vString
@
-}
getTokenValueVString :: MonadIO m => TokenValue -> m (Maybe T.Text)
getTokenValueVString s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

{- |
Set the value of the “@v_string@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vString 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVString :: MonadIO m => TokenValue -> CString -> m ()
setTokenValueVString s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CString)

{- |
Set the value of the “@v_string@” 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' #vString
@
-}
clearTokenValueVString :: MonadIO m => TokenValue -> m ()
clearTokenValueVString s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data TokenValueVStringFieldInfo
instance AttrInfo TokenValueVStringFieldInfo where
    type AttrAllowedOps TokenValueVStringFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TokenValueVStringFieldInfo = (~) CString
    type AttrBaseTypeConstraint TokenValueVStringFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVStringFieldInfo = Maybe T.Text
    type AttrLabel TokenValueVStringFieldInfo = "v_string"
    type AttrOrigin TokenValueVStringFieldInfo = TokenValue
    attrGet _ = getTokenValueVString
    attrSet _ = setTokenValueVString
    attrConstruct = undefined
    attrClear _ = clearTokenValueVString

tokenValue_vString :: AttrLabelProxy "vString"
tokenValue_vString = AttrLabelProxy

#endif


{- |
Get the value of the “@v_comment@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vComment
@
-}
getTokenValueVComment :: MonadIO m => TokenValue -> m (Maybe T.Text)
getTokenValueVComment s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

{- |
Set the value of the “@v_comment@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vComment 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVComment :: MonadIO m => TokenValue -> CString -> m ()
setTokenValueVComment s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CString)

{- |
Set the value of the “@v_comment@” 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' #vComment
@
-}
clearTokenValueVComment :: MonadIO m => TokenValue -> m ()
clearTokenValueVComment s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data TokenValueVCommentFieldInfo
instance AttrInfo TokenValueVCommentFieldInfo where
    type AttrAllowedOps TokenValueVCommentFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TokenValueVCommentFieldInfo = (~) CString
    type AttrBaseTypeConstraint TokenValueVCommentFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVCommentFieldInfo = Maybe T.Text
    type AttrLabel TokenValueVCommentFieldInfo = "v_comment"
    type AttrOrigin TokenValueVCommentFieldInfo = TokenValue
    attrGet _ = getTokenValueVComment
    attrSet _ = setTokenValueVComment
    attrConstruct = undefined
    attrClear _ = clearTokenValueVComment

tokenValue_vComment :: AttrLabelProxy "vComment"
tokenValue_vComment = AttrLabelProxy

#endif


{- |
Get the value of the “@v_char@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vChar
@
-}
getTokenValueVChar :: MonadIO m => TokenValue -> m Word8
getTokenValueVChar s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Word8
    return val

{- |
Set the value of the “@v_char@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vChar 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVChar :: MonadIO m => TokenValue -> Word8 -> m ()
setTokenValueVChar s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Word8)

#if ENABLE_OVERLOADING
data TokenValueVCharFieldInfo
instance AttrInfo TokenValueVCharFieldInfo where
    type AttrAllowedOps TokenValueVCharFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TokenValueVCharFieldInfo = (~) Word8
    type AttrBaseTypeConstraint TokenValueVCharFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVCharFieldInfo = Word8
    type AttrLabel TokenValueVCharFieldInfo = "v_char"
    type AttrOrigin TokenValueVCharFieldInfo = TokenValue
    attrGet _ = getTokenValueVChar
    attrSet _ = setTokenValueVChar
    attrConstruct = undefined
    attrClear _ = undefined

tokenValue_vChar :: AttrLabelProxy "vChar"
tokenValue_vChar = AttrLabelProxy

#endif


{- |
Get the value of the “@v_error@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' tokenValue #vError
@
-}
getTokenValueVError :: MonadIO m => TokenValue -> m Word32
getTokenValueVError s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Word32
    return val

{- |
Set the value of the “@v_error@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' tokenValue [ #vError 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTokenValueVError :: MonadIO m => TokenValue -> Word32 -> m ()
setTokenValueVError s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Word32)

#if ENABLE_OVERLOADING
data TokenValueVErrorFieldInfo
instance AttrInfo TokenValueVErrorFieldInfo where
    type AttrAllowedOps TokenValueVErrorFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TokenValueVErrorFieldInfo = (~) Word32
    type AttrBaseTypeConstraint TokenValueVErrorFieldInfo = (~) TokenValue
    type AttrGetType TokenValueVErrorFieldInfo = Word32
    type AttrLabel TokenValueVErrorFieldInfo = "v_error"
    type AttrOrigin TokenValueVErrorFieldInfo = TokenValue
    attrGet _ = getTokenValueVError
    attrSet _ = setTokenValueVError
    attrConstruct = undefined
    attrClear _ = undefined

tokenValue_vError :: AttrLabelProxy "vError"
tokenValue_vError = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList TokenValue
type instance O.AttributeList TokenValue = TokenValueAttributeList
type TokenValueAttributeList = ('[ '("vSymbol", TokenValueVSymbolFieldInfo), '("vIdentifier", TokenValueVIdentifierFieldInfo), '("vBinary", TokenValueVBinaryFieldInfo), '("vOctal", TokenValueVOctalFieldInfo), '("vInt", TokenValueVIntFieldInfo), '("vInt64", TokenValueVInt64FieldInfo), '("vFloat", TokenValueVFloatFieldInfo), '("vHex", TokenValueVHexFieldInfo), '("vString", TokenValueVStringFieldInfo), '("vComment", TokenValueVCommentFieldInfo), '("vChar", TokenValueVCharFieldInfo), '("vError", TokenValueVErrorFieldInfo)] :: [(Symbol, *)])
#endif

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

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