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

Specifies the 'GI.GLib.Structs.Scanner.Scanner' parser configuration. Most settings can
be changed during the parsing phase and will affect the lexical
parsing of the next unpeeked token.
-}

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

module GI.GLib.Structs.ScannerConfig
    (

-- * Exported types
    ScannerConfig(..)                       ,
    newZeroScannerConfig                    ,
    noScannerConfig                         ,


 -- * Properties
-- ** caseSensitive #attr:caseSensitive#
{- | specifies if symbols are case sensitive (the
    default is 'False').
-}
    getScannerConfigCaseSensitive           ,
#if ENABLE_OVERLOADING
    scannerConfig_caseSensitive             ,
#endif
    setScannerConfigCaseSensitive           ,


-- ** char2Token #attr:char2Token#
{- | specifies if characters are reported by setting
    @token = ch@ or as 'GI.GLib.Enums.TokenTypeChar' (the default is 'True').
-}
    getScannerConfigChar2Token              ,
#if ENABLE_OVERLOADING
    scannerConfig_char2Token                ,
#endif
    setScannerConfigChar2Token              ,


-- ** cpairCommentSingle #attr:cpairCommentSingle#
{- | specifies the characters at the start and
    end of single-line comments. The default is \"#\\n\" which means
    that single-line comments start with a \'#\' and continue until
    a \'\\n\' (end of line).
-}
    clearScannerConfigCpairCommentSingle    ,
    getScannerConfigCpairCommentSingle      ,
#if ENABLE_OVERLOADING
    scannerConfig_cpairCommentSingle        ,
#endif
    setScannerConfigCpairCommentSingle      ,


-- ** csetIdentifierFirst #attr:csetIdentifierFirst#
{- | specifies the characters which can start
    identifiers (the default is 'GI.GLib.Constants.CSET_a_2_z', \"_\", and 'GI.GLib.Constants.CSET_A_2_Z').
-}
    clearScannerConfigCsetIdentifierFirst   ,
    getScannerConfigCsetIdentifierFirst     ,
#if ENABLE_OVERLOADING
    scannerConfig_csetIdentifierFirst       ,
#endif
    setScannerConfigCsetIdentifierFirst     ,


-- ** csetIdentifierNth #attr:csetIdentifierNth#
{- | specifies the characters which can be used
    in identifiers, after the first character (the default is
    'GI.GLib.Constants.CSET_a_2_z', \"_0123456789\", 'GI.GLib.Constants.CSET_A_2_Z', @/G_CSET_LATINS/@,
    @/G_CSET_LATINC/@).
-}
    clearScannerConfigCsetIdentifierNth     ,
    getScannerConfigCsetIdentifierNth       ,
#if ENABLE_OVERLOADING
    scannerConfig_csetIdentifierNth         ,
#endif
    setScannerConfigCsetIdentifierNth       ,


-- ** csetSkipCharacters #attr:csetSkipCharacters#
{- | specifies which characters should be skipped
    by the scanner (the default is the whitespace characters: space,
    tab, carriage-return and line-feed).
-}
    clearScannerConfigCsetSkipCharacters    ,
    getScannerConfigCsetSkipCharacters      ,
#if ENABLE_OVERLOADING
    scannerConfig_csetSkipCharacters        ,
#endif
    setScannerConfigCsetSkipCharacters      ,


-- ** identifier2String #attr:identifier2String#
{- | specifies if identifiers are reported as strings
    (the default is 'False').
-}
    getScannerConfigIdentifier2String       ,
#if ENABLE_OVERLOADING
    scannerConfig_identifier2String         ,
#endif
    setScannerConfigIdentifier2String       ,


-- ** int2Float #attr:int2Float#
{- | specifies if all numbers are reported as 'GI.GLib.Enums.TokenTypeFloat'
    (the default is 'False').
-}
    getScannerConfigInt2Float               ,
#if ENABLE_OVERLOADING
    scannerConfig_int2Float                 ,
#endif
    setScannerConfigInt2Float               ,


-- ** numbers2Int #attr:numbers2Int#
{- | specifies if binary, octal and hexadecimal numbers
    are reported as @/G_TOKEN_INT/@ (the default is 'True').
-}
    getScannerConfigNumbers2Int             ,
#if ENABLE_OVERLOADING
    scannerConfig_numbers2Int               ,
#endif
    setScannerConfigNumbers2Int             ,


-- ** scanBinary #attr:scanBinary#
{- | specifies if binary numbers are recognized (the
    default is 'False').
-}
    getScannerConfigScanBinary              ,
#if ENABLE_OVERLOADING
    scannerConfig_scanBinary                ,
#endif
    setScannerConfigScanBinary              ,


-- ** scanCommentMulti #attr:scanCommentMulti#
{- | specifies if multi-line comments are recognized
    (the default is 'True').
-}
    getScannerConfigScanCommentMulti        ,
#if ENABLE_OVERLOADING
    scannerConfig_scanCommentMulti          ,
#endif
    setScannerConfigScanCommentMulti        ,


-- ** scanFloat #attr:scanFloat#
{- | specifies if floating point numbers are recognized
    (the default is 'True').
-}
    getScannerConfigScanFloat               ,
#if ENABLE_OVERLOADING
    scannerConfig_scanFloat                 ,
#endif
    setScannerConfigScanFloat               ,


-- ** scanHex #attr:scanHex#
{- | specifies if hexadecimal numbers are recognized (the
    default is 'True').
-}
    getScannerConfigScanHex                 ,
#if ENABLE_OVERLOADING
    scannerConfig_scanHex                   ,
#endif
    setScannerConfigScanHex                 ,


-- ** scanHexDollar #attr:scanHexDollar#
{- | specifies if \'$\' is recognized as a prefix for
    hexadecimal numbers (the default is 'False').
-}
    getScannerConfigScanHexDollar           ,
#if ENABLE_OVERLOADING
    scannerConfig_scanHexDollar             ,
#endif
    setScannerConfigScanHexDollar           ,


-- ** scanIdentifier #attr:scanIdentifier#
{- | specifies if identifiers are recognized (the
    default is 'True').
-}
    getScannerConfigScanIdentifier          ,
#if ENABLE_OVERLOADING
    scannerConfig_scanIdentifier            ,
#endif
    setScannerConfigScanIdentifier          ,


-- ** scanIdentifier1char #attr:scanIdentifier1char#
{- | specifies if single-character
    identifiers are recognized (the default is 'False').
-}
    getScannerConfigScanIdentifier1char     ,
#if ENABLE_OVERLOADING
    scannerConfig_scanIdentifier1char       ,
#endif
    setScannerConfigScanIdentifier1char     ,


-- ** scanIdentifierNULL #attr:scanIdentifierNULL#
{- | specifies if 'Nothing' is reported as
    'GI.GLib.Enums.TokenTypeIdentifierNull' (the default is 'False').
-}
    getScannerConfigScanIdentifierNULL      ,
#if ENABLE_OVERLOADING
    scannerConfig_scanIdentifierNULL        ,
#endif
    setScannerConfigScanIdentifierNULL      ,


-- ** scanOctal #attr:scanOctal#
{- | specifies if octal numbers are recognized (the
    default is 'True').
-}
    getScannerConfigScanOctal               ,
#if ENABLE_OVERLOADING
    scannerConfig_scanOctal                 ,
#endif
    setScannerConfigScanOctal               ,


-- ** scanStringDq #attr:scanStringDq#
{- | specifies if strings can be enclosed in double
    quotes (the default is 'True').
-}
    getScannerConfigScanStringDq            ,
#if ENABLE_OVERLOADING
    scannerConfig_scanStringDq              ,
#endif
    setScannerConfigScanStringDq            ,


-- ** scanStringSq #attr:scanStringSq#
{- | specifies if strings can be enclosed in single
    quotes (the default is 'True').
-}
    getScannerConfigScanStringSq            ,
#if ENABLE_OVERLOADING
    scannerConfig_scanStringSq              ,
#endif
    setScannerConfigScanStringSq            ,


-- ** scanSymbols #attr:scanSymbols#
{- | specifies if symbols are recognized (the default
    is 'True').
-}
    getScannerConfigScanSymbols             ,
#if ENABLE_OVERLOADING
    scannerConfig_scanSymbols               ,
#endif
    setScannerConfigScanSymbols             ,


-- ** scope0Fallback #attr:scope0Fallback#
{- | specifies if a symbol is searched for in the
    default scope in addition to the current scope (the default is 'False').
-}
    getScannerConfigScope0Fallback          ,
#if ENABLE_OVERLOADING
    scannerConfig_scope0Fallback            ,
#endif
    setScannerConfigScope0Fallback          ,


-- ** skipCommentMulti #attr:skipCommentMulti#
{- | specifies if multi-line comments are skipped
    and not returned as tokens (the default is 'True').
-}
    getScannerConfigSkipCommentMulti        ,
#if ENABLE_OVERLOADING
    scannerConfig_skipCommentMulti          ,
#endif
    setScannerConfigSkipCommentMulti        ,


-- ** skipCommentSingle #attr:skipCommentSingle#
{- | specifies if single-line comments are skipped
    and not returned as tokens (the default is 'True').
-}
    getScannerConfigSkipCommentSingle       ,
#if ENABLE_OVERLOADING
    scannerConfig_skipCommentSingle         ,
#endif
    setScannerConfigSkipCommentSingle       ,


-- ** storeInt64 #attr:storeInt64#
{- | use value.v_int64 rather than v_int
-}
    getScannerConfigStoreInt64              ,
#if ENABLE_OVERLOADING
    scannerConfig_storeInt64                ,
#endif
    setScannerConfigStoreInt64              ,


-- ** symbol2Token #attr:symbol2Token#
{- | specifies if symbols are reported by setting
    @token = v_symbol@ or as 'GI.GLib.Enums.TokenTypeSymbol' (the default is 'False').
-}
    getScannerConfigSymbol2Token            ,
#if ENABLE_OVERLOADING
    scannerConfig_symbol2Token              ,
#endif
    setScannerConfigSymbol2Token            ,




    ) 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 ScannerConfig = ScannerConfig (ManagedPtr ScannerConfig)
instance WrappedPtr ScannerConfig where
    wrappedPtrCalloc = callocBytes 128
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 128 >=> wrapPtr ScannerConfig)
    wrappedPtrFree = Just ptr_to_g_free

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `ScannerConfig`.
noScannerConfig :: Maybe ScannerConfig
noScannerConfig = Nothing

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

@
'Data.GI.Base.Attributes.get' scannerConfig #csetSkipCharacters
@
-}
getScannerConfigCsetSkipCharacters :: MonadIO m => ScannerConfig -> m (Maybe T.Text)
getScannerConfigCsetSkipCharacters 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 “@cset_skip_characters@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

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

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

#if ENABLE_OVERLOADING
data ScannerConfigCsetSkipCharactersFieldInfo
instance AttrInfo ScannerConfigCsetSkipCharactersFieldInfo where
    type AttrAllowedOps ScannerConfigCsetSkipCharactersFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerConfigCsetSkipCharactersFieldInfo = (~) CString
    type AttrBaseTypeConstraint ScannerConfigCsetSkipCharactersFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigCsetSkipCharactersFieldInfo = Maybe T.Text
    type AttrLabel ScannerConfigCsetSkipCharactersFieldInfo = "cset_skip_characters"
    type AttrOrigin ScannerConfigCsetSkipCharactersFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigCsetSkipCharacters
    attrSet _ = setScannerConfigCsetSkipCharacters
    attrConstruct = undefined
    attrClear _ = clearScannerConfigCsetSkipCharacters

scannerConfig_csetSkipCharacters :: AttrLabelProxy "csetSkipCharacters"
scannerConfig_csetSkipCharacters = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #csetIdentifierFirst
@
-}
getScannerConfigCsetIdentifierFirst :: MonadIO m => ScannerConfig -> m (Maybe T.Text)
getScannerConfigCsetIdentifierFirst 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 “@cset_identifier_first@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' scannerConfig [ #csetIdentifierFirst 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigCsetIdentifierFirst :: MonadIO m => ScannerConfig -> CString -> m ()
setScannerConfigCsetIdentifierFirst s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: CString)

{- |
Set the value of the “@cset_identifier_first@” 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' #csetIdentifierFirst
@
-}
clearScannerConfigCsetIdentifierFirst :: MonadIO m => ScannerConfig -> m ()
clearScannerConfigCsetIdentifierFirst s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ScannerConfigCsetIdentifierFirstFieldInfo
instance AttrInfo ScannerConfigCsetIdentifierFirstFieldInfo where
    type AttrAllowedOps ScannerConfigCsetIdentifierFirstFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerConfigCsetIdentifierFirstFieldInfo = (~) CString
    type AttrBaseTypeConstraint ScannerConfigCsetIdentifierFirstFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigCsetIdentifierFirstFieldInfo = Maybe T.Text
    type AttrLabel ScannerConfigCsetIdentifierFirstFieldInfo = "cset_identifier_first"
    type AttrOrigin ScannerConfigCsetIdentifierFirstFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigCsetIdentifierFirst
    attrSet _ = setScannerConfigCsetIdentifierFirst
    attrConstruct = undefined
    attrClear _ = clearScannerConfigCsetIdentifierFirst

scannerConfig_csetIdentifierFirst :: AttrLabelProxy "csetIdentifierFirst"
scannerConfig_csetIdentifierFirst = AttrLabelProxy

#endif


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

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

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #csetIdentifierNth 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigCsetIdentifierNth :: MonadIO m => ScannerConfig -> CString -> m ()
setScannerConfigCsetIdentifierNth s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: CString)

{- |
Set the value of the “@cset_identifier_nth@” 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' #csetIdentifierNth
@
-}
clearScannerConfigCsetIdentifierNth :: MonadIO m => ScannerConfig -> m ()
clearScannerConfigCsetIdentifierNth s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ScannerConfigCsetIdentifierNthFieldInfo
instance AttrInfo ScannerConfigCsetIdentifierNthFieldInfo where
    type AttrAllowedOps ScannerConfigCsetIdentifierNthFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerConfigCsetIdentifierNthFieldInfo = (~) CString
    type AttrBaseTypeConstraint ScannerConfigCsetIdentifierNthFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigCsetIdentifierNthFieldInfo = Maybe T.Text
    type AttrLabel ScannerConfigCsetIdentifierNthFieldInfo = "cset_identifier_nth"
    type AttrOrigin ScannerConfigCsetIdentifierNthFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigCsetIdentifierNth
    attrSet _ = setScannerConfigCsetIdentifierNth
    attrConstruct = undefined
    attrClear _ = clearScannerConfigCsetIdentifierNth

scannerConfig_csetIdentifierNth :: AttrLabelProxy "csetIdentifierNth"
scannerConfig_csetIdentifierNth = AttrLabelProxy

#endif


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

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

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #cpairCommentSingle 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigCpairCommentSingle :: MonadIO m => ScannerConfig -> CString -> m ()
setScannerConfigCpairCommentSingle s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: CString)

{- |
Set the value of the “@cpair_comment_single@” 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' #cpairCommentSingle
@
-}
clearScannerConfigCpairCommentSingle :: MonadIO m => ScannerConfig -> m ()
clearScannerConfigCpairCommentSingle s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data ScannerConfigCpairCommentSingleFieldInfo
instance AttrInfo ScannerConfigCpairCommentSingleFieldInfo where
    type AttrAllowedOps ScannerConfigCpairCommentSingleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerConfigCpairCommentSingleFieldInfo = (~) CString
    type AttrBaseTypeConstraint ScannerConfigCpairCommentSingleFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigCpairCommentSingleFieldInfo = Maybe T.Text
    type AttrLabel ScannerConfigCpairCommentSingleFieldInfo = "cpair_comment_single"
    type AttrOrigin ScannerConfigCpairCommentSingleFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigCpairCommentSingle
    attrSet _ = setScannerConfigCpairCommentSingle
    attrConstruct = undefined
    attrClear _ = clearScannerConfigCpairCommentSingle

scannerConfig_cpairCommentSingle :: AttrLabelProxy "cpairCommentSingle"
scannerConfig_cpairCommentSingle = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #caseSensitive
@
-}
getScannerConfigCaseSensitive :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigCaseSensitive s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #caseSensitive 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigCaseSensitive :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigCaseSensitive s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigCaseSensitiveFieldInfo
instance AttrInfo ScannerConfigCaseSensitiveFieldInfo where
    type AttrAllowedOps ScannerConfigCaseSensitiveFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigCaseSensitiveFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigCaseSensitiveFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigCaseSensitiveFieldInfo = Word32
    type AttrLabel ScannerConfigCaseSensitiveFieldInfo = "case_sensitive"
    type AttrOrigin ScannerConfigCaseSensitiveFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigCaseSensitive
    attrSet _ = setScannerConfigCaseSensitive
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_caseSensitive :: AttrLabelProxy "caseSensitive"
scannerConfig_caseSensitive = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #skipCommentMulti
@
-}
getScannerConfigSkipCommentMulti :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigSkipCommentMulti s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 36) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #skipCommentMulti 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigSkipCommentMulti :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigSkipCommentMulti s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 36) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigSkipCommentMultiFieldInfo
instance AttrInfo ScannerConfigSkipCommentMultiFieldInfo where
    type AttrAllowedOps ScannerConfigSkipCommentMultiFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigSkipCommentMultiFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigSkipCommentMultiFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigSkipCommentMultiFieldInfo = Word32
    type AttrLabel ScannerConfigSkipCommentMultiFieldInfo = "skip_comment_multi"
    type AttrOrigin ScannerConfigSkipCommentMultiFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigSkipCommentMulti
    attrSet _ = setScannerConfigSkipCommentMulti
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_skipCommentMulti :: AttrLabelProxy "skipCommentMulti"
scannerConfig_skipCommentMulti = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #skipCommentSingle
@
-}
getScannerConfigSkipCommentSingle :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigSkipCommentSingle s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #skipCommentSingle 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigSkipCommentSingle :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigSkipCommentSingle s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigSkipCommentSingleFieldInfo
instance AttrInfo ScannerConfigSkipCommentSingleFieldInfo where
    type AttrAllowedOps ScannerConfigSkipCommentSingleFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigSkipCommentSingleFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigSkipCommentSingleFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigSkipCommentSingleFieldInfo = Word32
    type AttrLabel ScannerConfigSkipCommentSingleFieldInfo = "skip_comment_single"
    type AttrOrigin ScannerConfigSkipCommentSingleFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigSkipCommentSingle
    attrSet _ = setScannerConfigSkipCommentSingle
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_skipCommentSingle :: AttrLabelProxy "skipCommentSingle"
scannerConfig_skipCommentSingle = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanCommentMulti
@
-}
getScannerConfigScanCommentMulti :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanCommentMulti s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 44) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanCommentMulti 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanCommentMulti :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanCommentMulti s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 44) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanCommentMultiFieldInfo
instance AttrInfo ScannerConfigScanCommentMultiFieldInfo where
    type AttrAllowedOps ScannerConfigScanCommentMultiFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanCommentMultiFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanCommentMultiFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanCommentMultiFieldInfo = Word32
    type AttrLabel ScannerConfigScanCommentMultiFieldInfo = "scan_comment_multi"
    type AttrOrigin ScannerConfigScanCommentMultiFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanCommentMulti
    attrSet _ = setScannerConfigScanCommentMulti
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanCommentMulti :: AttrLabelProxy "scanCommentMulti"
scannerConfig_scanCommentMulti = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanIdentifier
@
-}
getScannerConfigScanIdentifier :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanIdentifier s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanIdentifier 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanIdentifier :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanIdentifier s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanIdentifierFieldInfo
instance AttrInfo ScannerConfigScanIdentifierFieldInfo where
    type AttrAllowedOps ScannerConfigScanIdentifierFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanIdentifierFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanIdentifierFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanIdentifierFieldInfo = Word32
    type AttrLabel ScannerConfigScanIdentifierFieldInfo = "scan_identifier"
    type AttrOrigin ScannerConfigScanIdentifierFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanIdentifier
    attrSet _ = setScannerConfigScanIdentifier
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanIdentifier :: AttrLabelProxy "scanIdentifier"
scannerConfig_scanIdentifier = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanIdentifier1char
@
-}
getScannerConfigScanIdentifier1char :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanIdentifier1char s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 52) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanIdentifier1char 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanIdentifier1char :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanIdentifier1char s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 52) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanIdentifier1charFieldInfo
instance AttrInfo ScannerConfigScanIdentifier1charFieldInfo where
    type AttrAllowedOps ScannerConfigScanIdentifier1charFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanIdentifier1charFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanIdentifier1charFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanIdentifier1charFieldInfo = Word32
    type AttrLabel ScannerConfigScanIdentifier1charFieldInfo = "scan_identifier_1char"
    type AttrOrigin ScannerConfigScanIdentifier1charFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanIdentifier1char
    attrSet _ = setScannerConfigScanIdentifier1char
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanIdentifier1char :: AttrLabelProxy "scanIdentifier1char"
scannerConfig_scanIdentifier1char = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanIdentifierNULL
@
-}
getScannerConfigScanIdentifierNULL :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanIdentifierNULL s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanIdentifierNULL 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanIdentifierNULL :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanIdentifierNULL s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanIdentifierNULLFieldInfo
instance AttrInfo ScannerConfigScanIdentifierNULLFieldInfo where
    type AttrAllowedOps ScannerConfigScanIdentifierNULLFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanIdentifierNULLFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanIdentifierNULLFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanIdentifierNULLFieldInfo = Word32
    type AttrLabel ScannerConfigScanIdentifierNULLFieldInfo = "scan_identifier_NULL"
    type AttrOrigin ScannerConfigScanIdentifierNULLFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanIdentifierNULL
    attrSet _ = setScannerConfigScanIdentifierNULL
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanIdentifierNULL :: AttrLabelProxy "scanIdentifierNULL"
scannerConfig_scanIdentifierNULL = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanSymbols
@
-}
getScannerConfigScanSymbols :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanSymbols s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 60) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanSymbols 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanSymbols :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanSymbols s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 60) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanSymbolsFieldInfo
instance AttrInfo ScannerConfigScanSymbolsFieldInfo where
    type AttrAllowedOps ScannerConfigScanSymbolsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanSymbolsFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanSymbolsFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanSymbolsFieldInfo = Word32
    type AttrLabel ScannerConfigScanSymbolsFieldInfo = "scan_symbols"
    type AttrOrigin ScannerConfigScanSymbolsFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanSymbols
    attrSet _ = setScannerConfigScanSymbols
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanSymbols :: AttrLabelProxy "scanSymbols"
scannerConfig_scanSymbols = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanBinary
@
-}
getScannerConfigScanBinary :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanBinary s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanBinary 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanBinary :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanBinary s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanBinaryFieldInfo
instance AttrInfo ScannerConfigScanBinaryFieldInfo where
    type AttrAllowedOps ScannerConfigScanBinaryFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanBinaryFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanBinaryFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanBinaryFieldInfo = Word32
    type AttrLabel ScannerConfigScanBinaryFieldInfo = "scan_binary"
    type AttrOrigin ScannerConfigScanBinaryFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanBinary
    attrSet _ = setScannerConfigScanBinary
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanBinary :: AttrLabelProxy "scanBinary"
scannerConfig_scanBinary = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanOctal
@
-}
getScannerConfigScanOctal :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanOctal s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 68) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanOctal 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanOctal :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanOctal s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 68) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanOctalFieldInfo
instance AttrInfo ScannerConfigScanOctalFieldInfo where
    type AttrAllowedOps ScannerConfigScanOctalFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanOctalFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanOctalFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanOctalFieldInfo = Word32
    type AttrLabel ScannerConfigScanOctalFieldInfo = "scan_octal"
    type AttrOrigin ScannerConfigScanOctalFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanOctal
    attrSet _ = setScannerConfigScanOctal
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanOctal :: AttrLabelProxy "scanOctal"
scannerConfig_scanOctal = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanFloat
@
-}
getScannerConfigScanFloat :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanFloat s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 72) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanFloat 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanFloat :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanFloat s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 72) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanFloatFieldInfo
instance AttrInfo ScannerConfigScanFloatFieldInfo where
    type AttrAllowedOps ScannerConfigScanFloatFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanFloatFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanFloatFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanFloatFieldInfo = Word32
    type AttrLabel ScannerConfigScanFloatFieldInfo = "scan_float"
    type AttrOrigin ScannerConfigScanFloatFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanFloat
    attrSet _ = setScannerConfigScanFloat
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanFloat :: AttrLabelProxy "scanFloat"
scannerConfig_scanFloat = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanHex
@
-}
getScannerConfigScanHex :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanHex s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 76) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanHex 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanHex :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanHex s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 76) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanHexFieldInfo
instance AttrInfo ScannerConfigScanHexFieldInfo where
    type AttrAllowedOps ScannerConfigScanHexFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanHexFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanHexFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanHexFieldInfo = Word32
    type AttrLabel ScannerConfigScanHexFieldInfo = "scan_hex"
    type AttrOrigin ScannerConfigScanHexFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanHex
    attrSet _ = setScannerConfigScanHex
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanHex :: AttrLabelProxy "scanHex"
scannerConfig_scanHex = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanHexDollar
@
-}
getScannerConfigScanHexDollar :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanHexDollar s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 80) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanHexDollar 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanHexDollar :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanHexDollar s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 80) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanHexDollarFieldInfo
instance AttrInfo ScannerConfigScanHexDollarFieldInfo where
    type AttrAllowedOps ScannerConfigScanHexDollarFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanHexDollarFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanHexDollarFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanHexDollarFieldInfo = Word32
    type AttrLabel ScannerConfigScanHexDollarFieldInfo = "scan_hex_dollar"
    type AttrOrigin ScannerConfigScanHexDollarFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanHexDollar
    attrSet _ = setScannerConfigScanHexDollar
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanHexDollar :: AttrLabelProxy "scanHexDollar"
scannerConfig_scanHexDollar = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanStringSq
@
-}
getScannerConfigScanStringSq :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanStringSq s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 84) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanStringSq 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanStringSq :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanStringSq s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 84) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanStringSqFieldInfo
instance AttrInfo ScannerConfigScanStringSqFieldInfo where
    type AttrAllowedOps ScannerConfigScanStringSqFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanStringSqFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanStringSqFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanStringSqFieldInfo = Word32
    type AttrLabel ScannerConfigScanStringSqFieldInfo = "scan_string_sq"
    type AttrOrigin ScannerConfigScanStringSqFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanStringSq
    attrSet _ = setScannerConfigScanStringSq
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanStringSq :: AttrLabelProxy "scanStringSq"
scannerConfig_scanStringSq = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scanStringDq
@
-}
getScannerConfigScanStringDq :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScanStringDq s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 88) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scanStringDq 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScanStringDq :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScanStringDq s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 88) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScanStringDqFieldInfo
instance AttrInfo ScannerConfigScanStringDqFieldInfo where
    type AttrAllowedOps ScannerConfigScanStringDqFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScanStringDqFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScanStringDqFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScanStringDqFieldInfo = Word32
    type AttrLabel ScannerConfigScanStringDqFieldInfo = "scan_string_dq"
    type AttrOrigin ScannerConfigScanStringDqFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScanStringDq
    attrSet _ = setScannerConfigScanStringDq
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scanStringDq :: AttrLabelProxy "scanStringDq"
scannerConfig_scanStringDq = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #numbers2Int
@
-}
getScannerConfigNumbers2Int :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigNumbers2Int s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 92) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #numbers2Int 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigNumbers2Int :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigNumbers2Int s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 92) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigNumbers2IntFieldInfo
instance AttrInfo ScannerConfigNumbers2IntFieldInfo where
    type AttrAllowedOps ScannerConfigNumbers2IntFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigNumbers2IntFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigNumbers2IntFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigNumbers2IntFieldInfo = Word32
    type AttrLabel ScannerConfigNumbers2IntFieldInfo = "numbers_2_int"
    type AttrOrigin ScannerConfigNumbers2IntFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigNumbers2Int
    attrSet _ = setScannerConfigNumbers2Int
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_numbers2Int :: AttrLabelProxy "numbers2Int"
scannerConfig_numbers2Int = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #int2Float
@
-}
getScannerConfigInt2Float :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigInt2Float s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 96) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #int2Float 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigInt2Float :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigInt2Float s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 96) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigInt2FloatFieldInfo
instance AttrInfo ScannerConfigInt2FloatFieldInfo where
    type AttrAllowedOps ScannerConfigInt2FloatFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigInt2FloatFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigInt2FloatFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigInt2FloatFieldInfo = Word32
    type AttrLabel ScannerConfigInt2FloatFieldInfo = "int_2_float"
    type AttrOrigin ScannerConfigInt2FloatFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigInt2Float
    attrSet _ = setScannerConfigInt2Float
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_int2Float :: AttrLabelProxy "int2Float"
scannerConfig_int2Float = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #identifier2String
@
-}
getScannerConfigIdentifier2String :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigIdentifier2String s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 100) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #identifier2String 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigIdentifier2String :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigIdentifier2String s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 100) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigIdentifier2StringFieldInfo
instance AttrInfo ScannerConfigIdentifier2StringFieldInfo where
    type AttrAllowedOps ScannerConfigIdentifier2StringFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigIdentifier2StringFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigIdentifier2StringFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigIdentifier2StringFieldInfo = Word32
    type AttrLabel ScannerConfigIdentifier2StringFieldInfo = "identifier_2_string"
    type AttrOrigin ScannerConfigIdentifier2StringFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigIdentifier2String
    attrSet _ = setScannerConfigIdentifier2String
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_identifier2String :: AttrLabelProxy "identifier2String"
scannerConfig_identifier2String = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #char2Token
@
-}
getScannerConfigChar2Token :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigChar2Token s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 104) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #char2Token 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigChar2Token :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigChar2Token s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 104) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigChar2TokenFieldInfo
instance AttrInfo ScannerConfigChar2TokenFieldInfo where
    type AttrAllowedOps ScannerConfigChar2TokenFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigChar2TokenFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigChar2TokenFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigChar2TokenFieldInfo = Word32
    type AttrLabel ScannerConfigChar2TokenFieldInfo = "char_2_token"
    type AttrOrigin ScannerConfigChar2TokenFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigChar2Token
    attrSet _ = setScannerConfigChar2Token
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_char2Token :: AttrLabelProxy "char2Token"
scannerConfig_char2Token = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #symbol2Token
@
-}
getScannerConfigSymbol2Token :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigSymbol2Token s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 108) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #symbol2Token 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigSymbol2Token :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigSymbol2Token s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 108) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigSymbol2TokenFieldInfo
instance AttrInfo ScannerConfigSymbol2TokenFieldInfo where
    type AttrAllowedOps ScannerConfigSymbol2TokenFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigSymbol2TokenFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigSymbol2TokenFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigSymbol2TokenFieldInfo = Word32
    type AttrLabel ScannerConfigSymbol2TokenFieldInfo = "symbol_2_token"
    type AttrOrigin ScannerConfigSymbol2TokenFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigSymbol2Token
    attrSet _ = setScannerConfigSymbol2Token
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_symbol2Token :: AttrLabelProxy "symbol2Token"
scannerConfig_symbol2Token = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #scope0Fallback
@
-}
getScannerConfigScope0Fallback :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigScope0Fallback s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 112) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #scope0Fallback 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigScope0Fallback :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigScope0Fallback s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 112) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigScope0FallbackFieldInfo
instance AttrInfo ScannerConfigScope0FallbackFieldInfo where
    type AttrAllowedOps ScannerConfigScope0FallbackFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigScope0FallbackFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigScope0FallbackFieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigScope0FallbackFieldInfo = Word32
    type AttrLabel ScannerConfigScope0FallbackFieldInfo = "scope_0_fallback"
    type AttrOrigin ScannerConfigScope0FallbackFieldInfo = ScannerConfig
    attrGet _ = getScannerConfigScope0Fallback
    attrSet _ = setScannerConfigScope0Fallback
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_scope0Fallback :: AttrLabelProxy "scope0Fallback"
scannerConfig_scope0Fallback = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scannerConfig #storeInt64
@
-}
getScannerConfigStoreInt64 :: MonadIO m => ScannerConfig -> m Word32
getScannerConfigStoreInt64 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 116) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scannerConfig [ #storeInt64 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfigStoreInt64 :: MonadIO m => ScannerConfig -> Word32 -> m ()
setScannerConfigStoreInt64 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 116) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerConfigStoreInt64FieldInfo
instance AttrInfo ScannerConfigStoreInt64FieldInfo where
    type AttrAllowedOps ScannerConfigStoreInt64FieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerConfigStoreInt64FieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerConfigStoreInt64FieldInfo = (~) ScannerConfig
    type AttrGetType ScannerConfigStoreInt64FieldInfo = Word32
    type AttrLabel ScannerConfigStoreInt64FieldInfo = "store_int64"
    type AttrOrigin ScannerConfigStoreInt64FieldInfo = ScannerConfig
    attrGet _ = getScannerConfigStoreInt64
    attrSet _ = setScannerConfigStoreInt64
    attrConstruct = undefined
    attrClear _ = undefined

scannerConfig_storeInt64 :: AttrLabelProxy "storeInt64"
scannerConfig_storeInt64 = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList ScannerConfig
type instance O.AttributeList ScannerConfig = ScannerConfigAttributeList
type ScannerConfigAttributeList = ('[ '("csetSkipCharacters", ScannerConfigCsetSkipCharactersFieldInfo), '("csetIdentifierFirst", ScannerConfigCsetIdentifierFirstFieldInfo), '("csetIdentifierNth", ScannerConfigCsetIdentifierNthFieldInfo), '("cpairCommentSingle", ScannerConfigCpairCommentSingleFieldInfo), '("caseSensitive", ScannerConfigCaseSensitiveFieldInfo), '("skipCommentMulti", ScannerConfigSkipCommentMultiFieldInfo), '("skipCommentSingle", ScannerConfigSkipCommentSingleFieldInfo), '("scanCommentMulti", ScannerConfigScanCommentMultiFieldInfo), '("scanIdentifier", ScannerConfigScanIdentifierFieldInfo), '("scanIdentifier1char", ScannerConfigScanIdentifier1charFieldInfo), '("scanIdentifierNULL", ScannerConfigScanIdentifierNULLFieldInfo), '("scanSymbols", ScannerConfigScanSymbolsFieldInfo), '("scanBinary", ScannerConfigScanBinaryFieldInfo), '("scanOctal", ScannerConfigScanOctalFieldInfo), '("scanFloat", ScannerConfigScanFloatFieldInfo), '("scanHex", ScannerConfigScanHexFieldInfo), '("scanHexDollar", ScannerConfigScanHexDollarFieldInfo), '("scanStringSq", ScannerConfigScanStringSqFieldInfo), '("scanStringDq", ScannerConfigScanStringDqFieldInfo), '("numbers2Int", ScannerConfigNumbers2IntFieldInfo), '("int2Float", ScannerConfigInt2FloatFieldInfo), '("identifier2String", ScannerConfigIdentifier2StringFieldInfo), '("char2Token", ScannerConfigChar2TokenFieldInfo), '("symbol2Token", ScannerConfigSymbol2TokenFieldInfo), '("scope0Fallback", ScannerConfigScope0FallbackFieldInfo), '("storeInt64", ScannerConfigStoreInt64FieldInfo)] :: [(Symbol, *)])
#endif

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

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