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

The data structure representing a lexical scanner.

You should set /@inputName@/ after creating the scanner, since
it is used by the default message handler when displaying
warnings and errors. If you are scanning a file, the filename
would be a good choice.

The /@userData@/ and /@maxParseErrors@/ fields are not used.
If you need to associate extra data with the scanner you
can place them here.

If you want to use your own message handler you can set the
/@msgHandler@/ field. The type of the message handler function
is declared by 'GI.GLib.Callbacks.ScannerMsgFunc'.
-}

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

module GI.GLib.Structs.Scanner
    (

-- * Exported types
    Scanner(..)                             ,
    newZeroScanner                          ,
    noScanner                               ,


 -- * Methods
-- ** curLine #method:curLine#

#if ENABLE_OVERLOADING
    ScannerCurLineMethodInfo                ,
#endif
    scannerCurLine                          ,


-- ** curPosition #method:curPosition#

#if ENABLE_OVERLOADING
    ScannerCurPositionMethodInfo            ,
#endif
    scannerCurPosition                      ,


-- ** curToken #method:curToken#

#if ENABLE_OVERLOADING
    ScannerCurTokenMethodInfo               ,
#endif
    scannerCurToken                         ,


-- ** destroy #method:destroy#

#if ENABLE_OVERLOADING
    ScannerDestroyMethodInfo                ,
#endif
    scannerDestroy                          ,


-- ** eof #method:eof#

#if ENABLE_OVERLOADING
    ScannerEofMethodInfo                    ,
#endif
    scannerEof                              ,


-- ** getNextToken #method:getNextToken#

#if ENABLE_OVERLOADING
    ScannerGetNextTokenMethodInfo           ,
#endif
    scannerGetNextToken                     ,


-- ** inputFile #method:inputFile#

#if ENABLE_OVERLOADING
    ScannerInputFileMethodInfo              ,
#endif
    scannerInputFile                        ,


-- ** inputText #method:inputText#

#if ENABLE_OVERLOADING
    ScannerInputTextMethodInfo              ,
#endif
    scannerInputText                        ,


-- ** lookupSymbol #method:lookupSymbol#

#if ENABLE_OVERLOADING
    ScannerLookupSymbolMethodInfo           ,
#endif
    scannerLookupSymbol                     ,


-- ** peekNextToken #method:peekNextToken#

#if ENABLE_OVERLOADING
    ScannerPeekNextTokenMethodInfo          ,
#endif
    scannerPeekNextToken                    ,


-- ** scopeAddSymbol #method:scopeAddSymbol#

#if ENABLE_OVERLOADING
    ScannerScopeAddSymbolMethodInfo         ,
#endif
    scannerScopeAddSymbol                   ,


-- ** scopeLookupSymbol #method:scopeLookupSymbol#

#if ENABLE_OVERLOADING
    ScannerScopeLookupSymbolMethodInfo      ,
#endif
    scannerScopeLookupSymbol                ,


-- ** scopeRemoveSymbol #method:scopeRemoveSymbol#

#if ENABLE_OVERLOADING
    ScannerScopeRemoveSymbolMethodInfo      ,
#endif
    scannerScopeRemoveSymbol                ,


-- ** setScope #method:setScope#

#if ENABLE_OVERLOADING
    ScannerSetScopeMethodInfo               ,
#endif
    scannerSetScope                         ,


-- ** syncFileOffset #method:syncFileOffset#

#if ENABLE_OVERLOADING
    ScannerSyncFileOffsetMethodInfo         ,
#endif
    scannerSyncFileOffset                   ,


-- ** unexpToken #method:unexpToken#

#if ENABLE_OVERLOADING
    ScannerUnexpTokenMethodInfo             ,
#endif
    scannerUnexpToken                       ,




 -- * Properties
-- ** config #attr:config#
{- | link into the scanner configuration
-}
    clearScannerConfig                      ,
    getScannerConfig                        ,
#if ENABLE_OVERLOADING
    scanner_config                          ,
#endif
    setScannerConfig                        ,


-- ** inputName #attr:inputName#
{- | name of input stream, featured by the default message handler
-}
    clearScannerInputName                   ,
    getScannerInputName                     ,
#if ENABLE_OVERLOADING
    scanner_inputName                       ,
#endif
    setScannerInputName                     ,


-- ** line #attr:line#
{- | line number of the last token from 'GI.GLib.Structs.Scanner.scannerGetNextToken'
-}
    getScannerLine                          ,
#if ENABLE_OVERLOADING
    scanner_line                            ,
#endif
    setScannerLine                          ,


-- ** maxParseErrors #attr:maxParseErrors#
{- | unused
-}
    getScannerMaxParseErrors                ,
#if ENABLE_OVERLOADING
    scanner_maxParseErrors                  ,
#endif
    setScannerMaxParseErrors                ,


-- ** msgHandler #attr:msgHandler#
{- | handler function for _warn and _error
-}
    clearScannerMsgHandler                  ,
    getScannerMsgHandler                    ,
#if ENABLE_OVERLOADING
    scanner_msgHandler                      ,
#endif
    setScannerMsgHandler                    ,


-- ** nextLine #attr:nextLine#
{- | line number of the last token from 'GI.GLib.Structs.Scanner.scannerPeekNextToken'
-}
    getScannerNextLine                      ,
#if ENABLE_OVERLOADING
    scanner_nextLine                        ,
#endif
    setScannerNextLine                      ,


-- ** nextPosition #attr:nextPosition#
{- | char number of the last token from 'GI.GLib.Structs.Scanner.scannerPeekNextToken'
-}
    getScannerNextPosition                  ,
#if ENABLE_OVERLOADING
    scanner_nextPosition                    ,
#endif
    setScannerNextPosition                  ,


-- ** nextToken #attr:nextToken#
{- | token parsed by the last 'GI.GLib.Structs.Scanner.scannerPeekNextToken'
-}
    getScannerNextToken                     ,
#if ENABLE_OVERLOADING
    scanner_nextToken                       ,
#endif
    setScannerNextToken                     ,


-- ** nextValue #attr:nextValue#
{- | value of the last token from 'GI.GLib.Structs.Scanner.scannerPeekNextToken'
-}
    getScannerNextValue                     ,
#if ENABLE_OVERLOADING
    scanner_nextValue                       ,
#endif


-- ** parseErrors #attr:parseErrors#
{- | @/g_scanner_error()/@ increments this field
-}
    getScannerParseErrors                   ,
#if ENABLE_OVERLOADING
    scanner_parseErrors                     ,
#endif
    setScannerParseErrors                   ,


-- ** position #attr:position#
{- | char number of the last token from 'GI.GLib.Structs.Scanner.scannerGetNextToken'
-}
    getScannerPosition                      ,
#if ENABLE_OVERLOADING
    scanner_position                        ,
#endif
    setScannerPosition                      ,


-- ** qdata #attr:qdata#
{- | quarked data
-}
    clearScannerQdata                       ,
    getScannerQdata                         ,
#if ENABLE_OVERLOADING
    scanner_qdata                           ,
#endif
    setScannerQdata                         ,


-- ** token #attr:token#
{- | token parsed by the last 'GI.GLib.Structs.Scanner.scannerGetNextToken'
-}
    getScannerToken                         ,
#if ENABLE_OVERLOADING
    scanner_token                           ,
#endif
    setScannerToken                         ,


-- ** userData #attr:userData#
{- | unused
-}
    clearScannerUserData                    ,
    getScannerUserData                      ,
#if ENABLE_OVERLOADING
    scanner_userData                        ,
#endif
    setScannerUserData                      ,


-- ** value #attr:value#
{- | value of the last token from 'GI.GLib.Structs.Scanner.scannerGetNextToken'
-}
    getScannerValue                         ,
#if ENABLE_OVERLOADING
    scanner_value                           ,
#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

import qualified GI.GLib.Callbacks as GLib.Callbacks
import {-# SOURCE #-} qualified GI.GLib.Enums as GLib.Enums
import {-# SOURCE #-} qualified GI.GLib.Structs.Data as GLib.Data
import {-# SOURCE #-} qualified GI.GLib.Structs.ScannerConfig as GLib.ScannerConfig
import {-# SOURCE #-} qualified GI.GLib.Unions.TokenValue as GLib.TokenValue

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `Scanner`.
noScanner :: Maybe Scanner
noScanner = Nothing

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

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

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

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

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

#if ENABLE_OVERLOADING
data ScannerUserDataFieldInfo
instance AttrInfo ScannerUserDataFieldInfo where
    type AttrAllowedOps ScannerUserDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerUserDataFieldInfo = (~) (Ptr ())
    type AttrBaseTypeConstraint ScannerUserDataFieldInfo = (~) Scanner
    type AttrGetType ScannerUserDataFieldInfo = Ptr ()
    type AttrLabel ScannerUserDataFieldInfo = "user_data"
    type AttrOrigin ScannerUserDataFieldInfo = Scanner
    attrGet _ = getScannerUserData
    attrSet _ = setScannerUserData
    attrConstruct = undefined
    attrClear _ = clearScannerUserData

scanner_userData :: AttrLabelProxy "userData"
scanner_userData = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #maxParseErrors
@
-}
getScannerMaxParseErrors :: MonadIO m => Scanner -> m Word32
getScannerMaxParseErrors s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scanner [ #maxParseErrors 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerMaxParseErrors :: MonadIO m => Scanner -> Word32 -> m ()
setScannerMaxParseErrors s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerMaxParseErrorsFieldInfo
instance AttrInfo ScannerMaxParseErrorsFieldInfo where
    type AttrAllowedOps ScannerMaxParseErrorsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerMaxParseErrorsFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerMaxParseErrorsFieldInfo = (~) Scanner
    type AttrGetType ScannerMaxParseErrorsFieldInfo = Word32
    type AttrLabel ScannerMaxParseErrorsFieldInfo = "max_parse_errors"
    type AttrOrigin ScannerMaxParseErrorsFieldInfo = Scanner
    attrGet _ = getScannerMaxParseErrors
    attrSet _ = setScannerMaxParseErrors
    attrConstruct = undefined
    attrClear _ = undefined

scanner_maxParseErrors :: AttrLabelProxy "maxParseErrors"
scanner_maxParseErrors = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #parseErrors
@
-}
getScannerParseErrors :: MonadIO m => Scanner -> m Word32
getScannerParseErrors s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO Word32
    return val

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

@
'Data.GI.Base.Attributes.set' scanner [ #parseErrors 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerParseErrors :: MonadIO m => Scanner -> Word32 -> m ()
setScannerParseErrors s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 12) (val :: Word32)

#if ENABLE_OVERLOADING
data ScannerParseErrorsFieldInfo
instance AttrInfo ScannerParseErrorsFieldInfo where
    type AttrAllowedOps ScannerParseErrorsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerParseErrorsFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerParseErrorsFieldInfo = (~) Scanner
    type AttrGetType ScannerParseErrorsFieldInfo = Word32
    type AttrLabel ScannerParseErrorsFieldInfo = "parse_errors"
    type AttrOrigin ScannerParseErrorsFieldInfo = Scanner
    attrGet _ = getScannerParseErrors
    attrSet _ = setScannerParseErrors
    attrConstruct = undefined
    attrClear _ = undefined

scanner_parseErrors :: AttrLabelProxy "parseErrors"
scanner_parseErrors = AttrLabelProxy

#endif


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

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

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

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

#if ENABLE_OVERLOADING
data ScannerInputNameFieldInfo
instance AttrInfo ScannerInputNameFieldInfo where
    type AttrAllowedOps ScannerInputNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerInputNameFieldInfo = (~) CString
    type AttrBaseTypeConstraint ScannerInputNameFieldInfo = (~) Scanner
    type AttrGetType ScannerInputNameFieldInfo = Maybe T.Text
    type AttrLabel ScannerInputNameFieldInfo = "input_name"
    type AttrOrigin ScannerInputNameFieldInfo = Scanner
    attrGet _ = getScannerInputName
    attrSet _ = setScannerInputName
    attrConstruct = undefined
    attrClear _ = clearScannerInputName

scanner_inputName :: AttrLabelProxy "inputName"
scanner_inputName = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #qdata
@
-}
getScannerQdata :: MonadIO m => Scanner -> m (Maybe GLib.Data.Data)
getScannerQdata s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (Ptr GLib.Data.Data)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr GLib.Data.Data) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' scanner [ #qdata 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerQdata :: MonadIO m => Scanner -> Ptr GLib.Data.Data -> m ()
setScannerQdata s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Ptr GLib.Data.Data)

{- |
Set the value of the “@qdata@” 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' #qdata
@
-}
clearScannerQdata :: MonadIO m => Scanner -> m ()
clearScannerQdata s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullPtr :: Ptr GLib.Data.Data)

#if ENABLE_OVERLOADING
data ScannerQdataFieldInfo
instance AttrInfo ScannerQdataFieldInfo where
    type AttrAllowedOps ScannerQdataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerQdataFieldInfo = (~) (Ptr GLib.Data.Data)
    type AttrBaseTypeConstraint ScannerQdataFieldInfo = (~) Scanner
    type AttrGetType ScannerQdataFieldInfo = Maybe GLib.Data.Data
    type AttrLabel ScannerQdataFieldInfo = "qdata"
    type AttrOrigin ScannerQdataFieldInfo = Scanner
    attrGet _ = getScannerQdata
    attrSet _ = setScannerQdata
    attrConstruct = undefined
    attrClear _ = clearScannerQdata

scanner_qdata :: AttrLabelProxy "qdata"
scanner_qdata = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #config
@
-}
getScannerConfig :: MonadIO m => Scanner -> m (Maybe GLib.ScannerConfig.ScannerConfig)
getScannerConfig s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO (Ptr GLib.ScannerConfig.ScannerConfig)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr GLib.ScannerConfig.ScannerConfig) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' scanner [ #config 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerConfig :: MonadIO m => Scanner -> Ptr GLib.ScannerConfig.ScannerConfig -> m ()
setScannerConfig s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Ptr GLib.ScannerConfig.ScannerConfig)

{- |
Set the value of the “@config@” 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' #config
@
-}
clearScannerConfig :: MonadIO m => Scanner -> m ()
clearScannerConfig s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (FP.nullPtr :: Ptr GLib.ScannerConfig.ScannerConfig)

#if ENABLE_OVERLOADING
data ScannerConfigFieldInfo
instance AttrInfo ScannerConfigFieldInfo where
    type AttrAllowedOps ScannerConfigFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerConfigFieldInfo = (~) (Ptr GLib.ScannerConfig.ScannerConfig)
    type AttrBaseTypeConstraint ScannerConfigFieldInfo = (~) Scanner
    type AttrGetType ScannerConfigFieldInfo = Maybe GLib.ScannerConfig.ScannerConfig
    type AttrLabel ScannerConfigFieldInfo = "config"
    type AttrOrigin ScannerConfigFieldInfo = Scanner
    attrGet _ = getScannerConfig
    attrSet _ = setScannerConfig
    attrConstruct = undefined
    attrClear _ = clearScannerConfig

scanner_config :: AttrLabelProxy "config"
scanner_config = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #token
@
-}
getScannerToken :: MonadIO m => Scanner -> m GLib.Enums.TokenType
getScannerToken s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' scanner [ #token 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerToken :: MonadIO m => Scanner -> GLib.Enums.TokenType -> m ()
setScannerToken s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 40) (val' :: CUInt)

#if ENABLE_OVERLOADING
data ScannerTokenFieldInfo
instance AttrInfo ScannerTokenFieldInfo where
    type AttrAllowedOps ScannerTokenFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerTokenFieldInfo = (~) GLib.Enums.TokenType
    type AttrBaseTypeConstraint ScannerTokenFieldInfo = (~) Scanner
    type AttrGetType ScannerTokenFieldInfo = GLib.Enums.TokenType
    type AttrLabel ScannerTokenFieldInfo = "token"
    type AttrOrigin ScannerTokenFieldInfo = Scanner
    attrGet _ = getScannerToken
    attrSet _ = setScannerToken
    attrConstruct = undefined
    attrClear _ = undefined

scanner_token :: AttrLabelProxy "token"
scanner_token = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #value
@
-}
getScannerValue :: MonadIO m => Scanner -> m GLib.TokenValue.TokenValue
getScannerValue s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 48 :: (Ptr GLib.TokenValue.TokenValue)
    val' <- (newPtr GLib.TokenValue.TokenValue) val
    return val'

#if ENABLE_OVERLOADING
data ScannerValueFieldInfo
instance AttrInfo ScannerValueFieldInfo where
    type AttrAllowedOps ScannerValueFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint ScannerValueFieldInfo = (~) (Ptr GLib.TokenValue.TokenValue)
    type AttrBaseTypeConstraint ScannerValueFieldInfo = (~) Scanner
    type AttrGetType ScannerValueFieldInfo = GLib.TokenValue.TokenValue
    type AttrLabel ScannerValueFieldInfo = "value"
    type AttrOrigin ScannerValueFieldInfo = Scanner
    attrGet _ = getScannerValue
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

scanner_value :: AttrLabelProxy "value"
scanner_value = AttrLabelProxy

#endif


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

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

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

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

#if ENABLE_OVERLOADING
data ScannerLineFieldInfo
instance AttrInfo ScannerLineFieldInfo where
    type AttrAllowedOps ScannerLineFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerLineFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerLineFieldInfo = (~) Scanner
    type AttrGetType ScannerLineFieldInfo = Word32
    type AttrLabel ScannerLineFieldInfo = "line"
    type AttrOrigin ScannerLineFieldInfo = Scanner
    attrGet _ = getScannerLine
    attrSet _ = setScannerLine
    attrConstruct = undefined
    attrClear _ = undefined

scanner_line :: AttrLabelProxy "line"
scanner_line = AttrLabelProxy

#endif


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

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

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

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

#if ENABLE_OVERLOADING
data ScannerPositionFieldInfo
instance AttrInfo ScannerPositionFieldInfo where
    type AttrAllowedOps ScannerPositionFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerPositionFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerPositionFieldInfo = (~) Scanner
    type AttrGetType ScannerPositionFieldInfo = Word32
    type AttrLabel ScannerPositionFieldInfo = "position"
    type AttrOrigin ScannerPositionFieldInfo = Scanner
    attrGet _ = getScannerPosition
    attrSet _ = setScannerPosition
    attrConstruct = undefined
    attrClear _ = undefined

scanner_position :: AttrLabelProxy "position"
scanner_position = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #nextToken
@
-}
getScannerNextToken :: MonadIO m => Scanner -> m GLib.Enums.TokenType
getScannerNextToken s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' scanner [ #nextToken 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerNextToken :: MonadIO m => Scanner -> GLib.Enums.TokenType -> m ()
setScannerNextToken s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 64) (val' :: CUInt)

#if ENABLE_OVERLOADING
data ScannerNextTokenFieldInfo
instance AttrInfo ScannerNextTokenFieldInfo where
    type AttrAllowedOps ScannerNextTokenFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerNextTokenFieldInfo = (~) GLib.Enums.TokenType
    type AttrBaseTypeConstraint ScannerNextTokenFieldInfo = (~) Scanner
    type AttrGetType ScannerNextTokenFieldInfo = GLib.Enums.TokenType
    type AttrLabel ScannerNextTokenFieldInfo = "next_token"
    type AttrOrigin ScannerNextTokenFieldInfo = Scanner
    attrGet _ = getScannerNextToken
    attrSet _ = setScannerNextToken
    attrConstruct = undefined
    attrClear _ = undefined

scanner_nextToken :: AttrLabelProxy "nextToken"
scanner_nextToken = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #nextValue
@
-}
getScannerNextValue :: MonadIO m => Scanner -> m GLib.TokenValue.TokenValue
getScannerNextValue s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 72 :: (Ptr GLib.TokenValue.TokenValue)
    val' <- (newPtr GLib.TokenValue.TokenValue) val
    return val'

#if ENABLE_OVERLOADING
data ScannerNextValueFieldInfo
instance AttrInfo ScannerNextValueFieldInfo where
    type AttrAllowedOps ScannerNextValueFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint ScannerNextValueFieldInfo = (~) (Ptr GLib.TokenValue.TokenValue)
    type AttrBaseTypeConstraint ScannerNextValueFieldInfo = (~) Scanner
    type AttrGetType ScannerNextValueFieldInfo = GLib.TokenValue.TokenValue
    type AttrLabel ScannerNextValueFieldInfo = "next_value"
    type AttrOrigin ScannerNextValueFieldInfo = Scanner
    attrGet _ = getScannerNextValue
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

scanner_nextValue :: AttrLabelProxy "nextValue"
scanner_nextValue = AttrLabelProxy

#endif


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

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

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

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

#if ENABLE_OVERLOADING
data ScannerNextLineFieldInfo
instance AttrInfo ScannerNextLineFieldInfo where
    type AttrAllowedOps ScannerNextLineFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerNextLineFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerNextLineFieldInfo = (~) Scanner
    type AttrGetType ScannerNextLineFieldInfo = Word32
    type AttrLabel ScannerNextLineFieldInfo = "next_line"
    type AttrOrigin ScannerNextLineFieldInfo = Scanner
    attrGet _ = getScannerNextLine
    attrSet _ = setScannerNextLine
    attrConstruct = undefined
    attrClear _ = undefined

scanner_nextLine :: AttrLabelProxy "nextLine"
scanner_nextLine = AttrLabelProxy

#endif


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

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

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

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

#if ENABLE_OVERLOADING
data ScannerNextPositionFieldInfo
instance AttrInfo ScannerNextPositionFieldInfo where
    type AttrAllowedOps ScannerNextPositionFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint ScannerNextPositionFieldInfo = (~) Word32
    type AttrBaseTypeConstraint ScannerNextPositionFieldInfo = (~) Scanner
    type AttrGetType ScannerNextPositionFieldInfo = Word32
    type AttrLabel ScannerNextPositionFieldInfo = "next_position"
    type AttrOrigin ScannerNextPositionFieldInfo = Scanner
    attrGet _ = getScannerNextPosition
    attrSet _ = setScannerNextPosition
    attrConstruct = undefined
    attrClear _ = undefined

scanner_nextPosition :: AttrLabelProxy "nextPosition"
scanner_nextPosition = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' scanner #msgHandler
@
-}
getScannerMsgHandler :: MonadIO m => Scanner -> m (Maybe GLib.Callbacks.ScannerMsgFunc)
getScannerMsgHandler s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 136) :: IO (FunPtr GLib.Callbacks.C_ScannerMsgFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GLib.Callbacks.dynamic_ScannerMsgFunc val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' scanner [ #msgHandler 'Data.GI.Base.Attributes.:=' value ]
@
-}
setScannerMsgHandler :: MonadIO m => Scanner -> FunPtr GLib.Callbacks.C_ScannerMsgFunc -> m ()
setScannerMsgHandler s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 136) (val :: FunPtr GLib.Callbacks.C_ScannerMsgFunc)

{- |
Set the value of the “@msg_handler@” 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' #msgHandler
@
-}
clearScannerMsgHandler :: MonadIO m => Scanner -> m ()
clearScannerMsgHandler s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 136) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_ScannerMsgFunc)

#if ENABLE_OVERLOADING
data ScannerMsgHandlerFieldInfo
instance AttrInfo ScannerMsgHandlerFieldInfo where
    type AttrAllowedOps ScannerMsgHandlerFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ScannerMsgHandlerFieldInfo = (~) (FunPtr GLib.Callbacks.C_ScannerMsgFunc)
    type AttrBaseTypeConstraint ScannerMsgHandlerFieldInfo = (~) Scanner
    type AttrGetType ScannerMsgHandlerFieldInfo = Maybe GLib.Callbacks.ScannerMsgFunc
    type AttrLabel ScannerMsgHandlerFieldInfo = "msg_handler"
    type AttrOrigin ScannerMsgHandlerFieldInfo = Scanner
    attrGet _ = getScannerMsgHandler
    attrSet _ = setScannerMsgHandler
    attrConstruct = undefined
    attrClear _ = clearScannerMsgHandler

scanner_msgHandler :: AttrLabelProxy "msgHandler"
scanner_msgHandler = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList Scanner
type instance O.AttributeList Scanner = ScannerAttributeList
type ScannerAttributeList = ('[ '("userData", ScannerUserDataFieldInfo), '("maxParseErrors", ScannerMaxParseErrorsFieldInfo), '("parseErrors", ScannerParseErrorsFieldInfo), '("inputName", ScannerInputNameFieldInfo), '("qdata", ScannerQdataFieldInfo), '("config", ScannerConfigFieldInfo), '("token", ScannerTokenFieldInfo), '("value", ScannerValueFieldInfo), '("line", ScannerLineFieldInfo), '("position", ScannerPositionFieldInfo), '("nextToken", ScannerNextTokenFieldInfo), '("nextValue", ScannerNextValueFieldInfo), '("nextLine", ScannerNextLineFieldInfo), '("nextPosition", ScannerNextPositionFieldInfo), '("msgHandler", ScannerMsgHandlerFieldInfo)] :: [(Symbol, *)])
#endif

-- method Scanner::cur_line
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_cur_line" g_scanner_cur_line ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    IO Word32

{- |
Returns the current line in the input stream (counting
from 1). This is the line of the last token parsed via
'GI.GLib.Structs.Scanner.scannerGetNextToken'.
-}
scannerCurLine ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> m Word32
    {- ^ __Returns:__ the current line -}
scannerCurLine scanner = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    result <- g_scanner_cur_line scanner'
    touchManagedPtr scanner
    return result

#if ENABLE_OVERLOADING
data ScannerCurLineMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ScannerCurLineMethodInfo Scanner signature where
    overloadedMethod _ = scannerCurLine

#endif

-- method Scanner::cur_position
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_cur_position" g_scanner_cur_position ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    IO Word32

{- |
Returns the current position in the current line (counting
from 0). This is the position of the last token parsed via
'GI.GLib.Structs.Scanner.scannerGetNextToken'.
-}
scannerCurPosition ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> m Word32
    {- ^ __Returns:__ the current position on the line -}
scannerCurPosition scanner = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    result <- g_scanner_cur_position scanner'
    touchManagedPtr scanner
    return result

#if ENABLE_OVERLOADING
data ScannerCurPositionMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ScannerCurPositionMethodInfo Scanner signature where
    overloadedMethod _ = scannerCurPosition

#endif

-- method Scanner::cur_token
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "TokenType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_cur_token" g_scanner_cur_token ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    IO CUInt

{- |
Gets the current token type. This is simply the /@token@/
field in the 'GI.GLib.Structs.Scanner.Scanner' structure.
-}
scannerCurToken ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> m GLib.Enums.TokenType
    {- ^ __Returns:__ the current token type -}
scannerCurToken scanner = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    result <- g_scanner_cur_token scanner'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr scanner
    return result'

#if ENABLE_OVERLOADING
data ScannerCurTokenMethodInfo
instance (signature ~ (m GLib.Enums.TokenType), MonadIO m) => O.MethodInfo ScannerCurTokenMethodInfo Scanner signature where
    overloadedMethod _ = scannerCurToken

#endif

-- method Scanner::destroy
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_destroy" g_scanner_destroy ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    IO ()

{- |
Frees all memory used by the 'GI.GLib.Structs.Scanner.Scanner'.
-}
scannerDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> m ()
scannerDestroy scanner = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    g_scanner_destroy scanner'
    touchManagedPtr scanner
    return ()

#if ENABLE_OVERLOADING
data ScannerDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ScannerDestroyMethodInfo Scanner signature where
    overloadedMethod _ = scannerDestroy

#endif

-- method Scanner::eof
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_eof" g_scanner_eof ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    IO CInt

{- |
Returns 'True' if the scanner has reached the end of
the file or text buffer.
-}
scannerEof ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> m Bool
    {- ^ __Returns:__ 'True' if the scanner has reached the end of
    the file or text buffer -}
scannerEof scanner = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    result <- g_scanner_eof scanner'
    let result' = (/= 0) result
    touchManagedPtr scanner
    return result'

#if ENABLE_OVERLOADING
data ScannerEofMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo ScannerEofMethodInfo Scanner signature where
    overloadedMethod _ = scannerEof

#endif

-- method Scanner::get_next_token
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "TokenType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_get_next_token" g_scanner_get_next_token ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    IO CUInt

{- |
Parses the next token just like 'GI.GLib.Structs.Scanner.scannerPeekNextToken'
and also removes it from the input stream. The token data is
placed in the /@token@/, /@value@/, /@line@/, and /@position@/ fields of
the 'GI.GLib.Structs.Scanner.Scanner' structure.
-}
scannerGetNextToken ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> m GLib.Enums.TokenType
    {- ^ __Returns:__ the type of the token -}
scannerGetNextToken scanner = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    result <- g_scanner_get_next_token scanner'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr scanner
    return result'

#if ENABLE_OVERLOADING
data ScannerGetNextTokenMethodInfo
instance (signature ~ (m GLib.Enums.TokenType), MonadIO m) => O.MethodInfo ScannerGetNextTokenMethodInfo Scanner signature where
    overloadedMethod _ = scannerGetNextToken

#endif

-- method Scanner::input_file
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "input_fd", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a file descriptor", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_input_file" g_scanner_input_file ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    Int32 ->                                -- input_fd : TBasicType TInt
    IO ()

{- |
Prepares to scan a file.
-}
scannerInputFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> Int32
    {- ^ /@inputFd@/: a file descriptor -}
    -> m ()
scannerInputFile scanner inputFd = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    g_scanner_input_file scanner' inputFd
    touchManagedPtr scanner
    return ()

#if ENABLE_OVERLOADING
data ScannerInputFileMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m) => O.MethodInfo ScannerInputFileMethodInfo Scanner signature where
    overloadedMethod _ = scannerInputFile

#endif

-- method Scanner::input_text
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the text buffer to scan", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "text_len", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the length of the text buffer", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_input_text" g_scanner_input_text ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    CString ->                              -- text : TBasicType TUTF8
    Word32 ->                               -- text_len : TBasicType TUInt
    IO ()

{- |
Prepares to scan a text buffer.
-}
scannerInputText ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> T.Text
    {- ^ /@text@/: the text buffer to scan -}
    -> Word32
    {- ^ /@textLen@/: the length of the text buffer -}
    -> m ()
scannerInputText scanner text textLen = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    text' <- textToCString text
    g_scanner_input_text scanner' text' textLen
    touchManagedPtr scanner
    freeMem text'
    return ()

#if ENABLE_OVERLOADING
data ScannerInputTextMethodInfo
instance (signature ~ (T.Text -> Word32 -> m ()), MonadIO m) => O.MethodInfo ScannerInputTextMethodInfo Scanner signature where
    overloadedMethod _ = scannerInputText

#endif

-- method Scanner::lookup_symbol
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "symbol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the symbol to look up", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_lookup_symbol" g_scanner_lookup_symbol ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    CString ->                              -- symbol : TBasicType TUTF8
    IO (Ptr ())

{- |
Looks up a symbol in the current scope and return its value.
If the symbol is not bound in the current scope, 'Nothing' is
returned.
-}
scannerLookupSymbol ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> T.Text
    {- ^ /@symbol@/: the symbol to look up -}
    -> m (Ptr ())
    {- ^ __Returns:__ the value of /@symbol@/ in the current scope, or 'Nothing'
    if /@symbol@/ is not bound in the current scope -}
scannerLookupSymbol scanner symbol = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    symbol' <- textToCString symbol
    result <- g_scanner_lookup_symbol scanner' symbol'
    touchManagedPtr scanner
    freeMem symbol'
    return result

#if ENABLE_OVERLOADING
data ScannerLookupSymbolMethodInfo
instance (signature ~ (T.Text -> m (Ptr ())), MonadIO m) => O.MethodInfo ScannerLookupSymbolMethodInfo Scanner signature where
    overloadedMethod _ = scannerLookupSymbol

#endif

-- method Scanner::peek_next_token
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "GLib", name = "TokenType"}))
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_peek_next_token" g_scanner_peek_next_token ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    IO CUInt

{- |
Parses the next token, without removing it from the input stream.
The token data is placed in the /@nextToken@/, /@nextValue@/, /@nextLine@/,
and /@nextPosition@/ fields of the 'GI.GLib.Structs.Scanner.Scanner' structure.

Note that, while the token is not removed from the input stream
(i.e. the next call to 'GI.GLib.Structs.Scanner.scannerGetNextToken' will return the
same token), it will not be reevaluated. This can lead to surprising
results when changing scope or the scanner configuration after peeking
the next token. Getting the next token after switching the scope or
configuration will return whatever was peeked before, regardless of
any symbols that may have been added or removed in the new scope.
-}
scannerPeekNextToken ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> m GLib.Enums.TokenType
    {- ^ __Returns:__ the type of the token -}
scannerPeekNextToken scanner = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    result <- g_scanner_peek_next_token scanner'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr scanner
    return result'

#if ENABLE_OVERLOADING
data ScannerPeekNextTokenMethodInfo
instance (signature ~ (m GLib.Enums.TokenType), MonadIO m) => O.MethodInfo ScannerPeekNextTokenMethodInfo Scanner signature where
    overloadedMethod _ = scannerPeekNextToken

#endif

-- method Scanner::scope_add_symbol
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "scope_id", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the scope id", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "symbol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the symbol to add", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "value", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "the value of the symbol", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_scope_add_symbol" g_scanner_scope_add_symbol ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    Word32 ->                               -- scope_id : TBasicType TUInt
    CString ->                              -- symbol : TBasicType TUTF8
    Ptr () ->                               -- value : TBasicType TPtr
    IO ()

{- |
Adds a symbol to the given scope.
-}
scannerScopeAddSymbol ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> Word32
    {- ^ /@scopeId@/: the scope id -}
    -> T.Text
    {- ^ /@symbol@/: the symbol to add -}
    -> Ptr ()
    {- ^ /@value@/: the value of the symbol -}
    -> m ()
scannerScopeAddSymbol scanner scopeId symbol value = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    symbol' <- textToCString symbol
    g_scanner_scope_add_symbol scanner' scopeId symbol' value
    touchManagedPtr scanner
    freeMem symbol'
    return ()

#if ENABLE_OVERLOADING
data ScannerScopeAddSymbolMethodInfo
instance (signature ~ (Word32 -> T.Text -> Ptr () -> m ()), MonadIO m) => O.MethodInfo ScannerScopeAddSymbolMethodInfo Scanner signature where
    overloadedMethod _ = scannerScopeAddSymbol

#endif

-- method Scanner::scope_lookup_symbol
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "scope_id", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the scope id", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "symbol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the symbol to look up", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_scope_lookup_symbol" g_scanner_scope_lookup_symbol ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    Word32 ->                               -- scope_id : TBasicType TUInt
    CString ->                              -- symbol : TBasicType TUTF8
    IO (Ptr ())

{- |
Looks up a symbol in a scope and return its value. If the
symbol is not bound in the scope, 'Nothing' is returned.
-}
scannerScopeLookupSymbol ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> Word32
    {- ^ /@scopeId@/: the scope id -}
    -> T.Text
    {- ^ /@symbol@/: the symbol to look up -}
    -> m (Ptr ())
    {- ^ __Returns:__ the value of /@symbol@/ in the given scope, or 'Nothing'
    if /@symbol@/ is not bound in the given scope. -}
scannerScopeLookupSymbol scanner scopeId symbol = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    symbol' <- textToCString symbol
    result <- g_scanner_scope_lookup_symbol scanner' scopeId symbol'
    touchManagedPtr scanner
    freeMem symbol'
    return result

#if ENABLE_OVERLOADING
data ScannerScopeLookupSymbolMethodInfo
instance (signature ~ (Word32 -> T.Text -> m (Ptr ())), MonadIO m) => O.MethodInfo ScannerScopeLookupSymbolMethodInfo Scanner signature where
    overloadedMethod _ = scannerScopeLookupSymbol

#endif

-- method Scanner::scope_remove_symbol
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "scope_id", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the scope id", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "symbol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the symbol to remove", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_scope_remove_symbol" g_scanner_scope_remove_symbol ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    Word32 ->                               -- scope_id : TBasicType TUInt
    CString ->                              -- symbol : TBasicType TUTF8
    IO ()

{- |
Removes a symbol from a scope.
-}
scannerScopeRemoveSymbol ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> Word32
    {- ^ /@scopeId@/: the scope id -}
    -> T.Text
    {- ^ /@symbol@/: the symbol to remove -}
    -> m ()
scannerScopeRemoveSymbol scanner scopeId symbol = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    symbol' <- textToCString symbol
    g_scanner_scope_remove_symbol scanner' scopeId symbol'
    touchManagedPtr scanner
    freeMem symbol'
    return ()

#if ENABLE_OVERLOADING
data ScannerScopeRemoveSymbolMethodInfo
instance (signature ~ (Word32 -> T.Text -> m ()), MonadIO m) => O.MethodInfo ScannerScopeRemoveSymbolMethodInfo Scanner signature where
    overloadedMethod _ = scannerScopeRemoveSymbol

#endif

-- method Scanner::set_scope
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "scope_id", argType = TBasicType TUInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the new scope id", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_set_scope" g_scanner_set_scope ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    Word32 ->                               -- scope_id : TBasicType TUInt
    IO Word32

{- |
Sets the current scope.
-}
scannerSetScope ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> Word32
    {- ^ /@scopeId@/: the new scope id -}
    -> m Word32
    {- ^ __Returns:__ the old scope id -}
scannerSetScope scanner scopeId = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    result <- g_scanner_set_scope scanner' scopeId
    touchManagedPtr scanner
    return result

#if ENABLE_OVERLOADING
data ScannerSetScopeMethodInfo
instance (signature ~ (Word32 -> m Word32), MonadIO m) => O.MethodInfo ScannerSetScopeMethodInfo Scanner signature where
    overloadedMethod _ = scannerSetScope

#endif

-- method Scanner::sync_file_offset
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_sync_file_offset" g_scanner_sync_file_offset ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    IO ()

{- |
Rewinds the filedescriptor to the current buffer position
and blows the file read ahead buffer. This is useful for
third party uses of the scanners filedescriptor, which hooks
onto the current scanning position.
-}
scannerSyncFileOffset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> m ()
scannerSyncFileOffset scanner = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    g_scanner_sync_file_offset scanner'
    touchManagedPtr scanner
    return ()

#if ENABLE_OVERLOADING
data ScannerSyncFileOffsetMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ScannerSyncFileOffsetMethodInfo Scanner signature where
    overloadedMethod _ = scannerSyncFileOffset

#endif

-- method Scanner::unexp_token
-- method type : OrdinaryMethod
-- Args : [Arg {argCName = "scanner", argType = TInterface (Name {namespace = "GLib", name = "Scanner"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GScanner", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "expected_token", argType = TInterface (Name {namespace = "GLib", name = "TokenType"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the expected token", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "identifier_spec", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a string describing how the scanner's user\n    refers to identifiers (%NULL defaults to \"identifier\").\n    This is used if @expected_token is %G_TOKEN_IDENTIFIER or\n    %G_TOKEN_IDENTIFIER_NULL.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "symbol_spec", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a string describing how the scanner's user refers\n    to symbols (%NULL defaults to \"symbol\"). This is used if\n    @expected_token is %G_TOKEN_SYMBOL or any token value greater\n    than %G_TOKEN_LAST.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "symbol_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the name of the symbol, if the scanner's current\n    token is a symbol.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a message string to output at the end of the\n    warning/error, or %NULL.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "is_error", argType = TBasicType TInt, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "if %TRUE it is output as an error. If %FALSE it is\n    output as a warning.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_unexp_token" g_scanner_unexp_token ::
    Ptr Scanner ->                          -- scanner : TInterface (Name {namespace = "GLib", name = "Scanner"})
    CUInt ->                                -- expected_token : TInterface (Name {namespace = "GLib", name = "TokenType"})
    CString ->                              -- identifier_spec : TBasicType TUTF8
    CString ->                              -- symbol_spec : TBasicType TUTF8
    CString ->                              -- symbol_name : TBasicType TUTF8
    CString ->                              -- message : TBasicType TUTF8
    Int32 ->                                -- is_error : TBasicType TInt
    IO ()

{- |
Outputs a message through the scanner\'s msg_handler,
resulting from an unexpected token in the input stream.
Note that you should not call 'GI.GLib.Structs.Scanner.scannerPeekNextToken'
followed by 'GI.GLib.Structs.Scanner.scannerUnexpToken' without an intermediate
call to 'GI.GLib.Structs.Scanner.scannerGetNextToken', as 'GI.GLib.Structs.Scanner.scannerUnexpToken'
evaluates the scanner\'s current token (not the peeked token)
to construct part of the message.
-}
scannerUnexpToken ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Scanner
    {- ^ /@scanner@/: a 'GI.GLib.Structs.Scanner.Scanner' -}
    -> GLib.Enums.TokenType
    {- ^ /@expectedToken@/: the expected token -}
    -> T.Text
    {- ^ /@identifierSpec@/: a string describing how the scanner\'s user
    refers to identifiers ('Nothing' defaults to \"identifier\").
    This is used if /@expectedToken@/ is 'GI.GLib.Enums.TokenTypeIdentifier' or
    'GI.GLib.Enums.TokenTypeIdentifierNull'. -}
    -> T.Text
    {- ^ /@symbolSpec@/: a string describing how the scanner\'s user refers
    to symbols ('Nothing' defaults to \"symbol\"). This is used if
    /@expectedToken@/ is 'GI.GLib.Enums.TokenTypeSymbol' or any token value greater
    than @/G_TOKEN_LAST/@. -}
    -> T.Text
    {- ^ /@symbolName@/: the name of the symbol, if the scanner\'s current
    token is a symbol. -}
    -> T.Text
    {- ^ /@message@/: a message string to output at the end of the
    warning\/error, or 'Nothing'. -}
    -> Int32
    {- ^ /@isError@/: if 'True' it is output as an error. If 'False' it is
    output as a warning. -}
    -> m ()
scannerUnexpToken scanner expectedToken identifierSpec symbolSpec symbolName message isError = liftIO $ do
    scanner' <- unsafeManagedPtrGetPtr scanner
    let expectedToken' = (fromIntegral . fromEnum) expectedToken
    identifierSpec' <- textToCString identifierSpec
    symbolSpec' <- textToCString symbolSpec
    symbolName' <- textToCString symbolName
    message' <- textToCString message
    g_scanner_unexp_token scanner' expectedToken' identifierSpec' symbolSpec' symbolName' message' isError
    touchManagedPtr scanner
    freeMem identifierSpec'
    freeMem symbolSpec'
    freeMem symbolName'
    freeMem message'
    return ()

#if ENABLE_OVERLOADING
data ScannerUnexpTokenMethodInfo
instance (signature ~ (GLib.Enums.TokenType -> T.Text -> T.Text -> T.Text -> T.Text -> Int32 -> m ()), MonadIO m) => O.MethodInfo ScannerUnexpTokenMethodInfo Scanner signature where
    overloadedMethod _ = scannerUnexpToken

#endif

#if ENABLE_OVERLOADING
type family ResolveScannerMethod (t :: Symbol) (o :: *) :: * where
    ResolveScannerMethod "curLine" o = ScannerCurLineMethodInfo
    ResolveScannerMethod "curPosition" o = ScannerCurPositionMethodInfo
    ResolveScannerMethod "curToken" o = ScannerCurTokenMethodInfo
    ResolveScannerMethod "destroy" o = ScannerDestroyMethodInfo
    ResolveScannerMethod "eof" o = ScannerEofMethodInfo
    ResolveScannerMethod "inputFile" o = ScannerInputFileMethodInfo
    ResolveScannerMethod "inputText" o = ScannerInputTextMethodInfo
    ResolveScannerMethod "lookupSymbol" o = ScannerLookupSymbolMethodInfo
    ResolveScannerMethod "peekNextToken" o = ScannerPeekNextTokenMethodInfo
    ResolveScannerMethod "scopeAddSymbol" o = ScannerScopeAddSymbolMethodInfo
    ResolveScannerMethod "scopeLookupSymbol" o = ScannerScopeLookupSymbolMethodInfo
    ResolveScannerMethod "scopeRemoveSymbol" o = ScannerScopeRemoveSymbolMethodInfo
    ResolveScannerMethod "syncFileOffset" o = ScannerSyncFileOffsetMethodInfo
    ResolveScannerMethod "unexpToken" o = ScannerUnexpTokenMethodInfo
    ResolveScannerMethod "getNextToken" o = ScannerGetNextTokenMethodInfo
    ResolveScannerMethod "setScope" o = ScannerSetScopeMethodInfo
    ResolveScannerMethod l o = O.MethodResolutionFailed l o

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