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

The data structure representing a lexical scanner.

You should set @input_name 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 @user_data and @max_parse_errors 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
@msg_handler field. The type of the message handler function
is declared by #GScannerMsgFunc.
-}

module GI.GLib.Structs.Scanner
    ( 

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


 -- * Methods
-- ** scannerCurLine
    scannerCurLine                          ,


-- ** scannerCurPosition
    scannerCurPosition                      ,


-- ** scannerCurToken
    scannerCurToken                         ,


-- ** scannerDestroy
    scannerDestroy                          ,


-- ** scannerEof
    scannerEof                              ,


-- ** scannerGetNextToken
    scannerGetNextToken                     ,


-- ** scannerInputFile
    scannerInputFile                        ,


-- ** scannerInputText
    scannerInputText                        ,


-- ** scannerPeekNextToken
    scannerPeekNextToken                    ,


-- ** scannerScopeAddSymbol
    scannerScopeAddSymbol                   ,


-- ** scannerScopeRemoveSymbol
    scannerScopeRemoveSymbol                ,


-- ** scannerSetScope
    scannerSetScope                         ,


-- ** scannerSyncFileOffset
    scannerSyncFileOffset                   ,


-- ** scannerUnexpToken
    scannerUnexpToken                       ,




 -- * Properties
-- ** Config
    scannerReadConfig                       ,


-- ** InputName
    scannerReadInputName                    ,


-- ** Line
    scannerReadLine                         ,


-- ** MaxParseErrors
    scannerReadMaxParseErrors               ,


-- ** NextLine
    scannerReadNextLine                     ,


-- ** NextPosition
    scannerReadNextPosition                 ,


-- ** NextToken
    scannerReadNextToken                    ,


-- ** NextValue
    scannerReadNextValue                    ,


-- ** ParseErrors
    scannerReadParseErrors                  ,


-- ** Position
    scannerReadPosition                     ,


-- ** Qdata
    scannerReadQdata                        ,


-- ** Token
    scannerReadToken                        ,


-- ** UserData
    scannerReadUserData                     ,


-- ** Value
    scannerReadValue                        ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.GLib.Types
import GI.GLib.Callbacks

newtype Scanner = Scanner (ForeignPtr Scanner)
noScanner :: Maybe Scanner
noScanner = Nothing

scannerReadUserData :: Scanner -> IO (Ptr ())
scannerReadUserData s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr ())
    return val

scannerReadMaxParseErrors :: Scanner -> IO Word32
scannerReadMaxParseErrors s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO Word32
    return val

scannerReadParseErrors :: Scanner -> IO Word32
scannerReadParseErrors s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO Word32
    return val

scannerReadInputName :: Scanner -> IO T.Text
scannerReadInputName s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CString
    val' <- cstringToText val
    return val'

scannerReadQdata :: Scanner -> IO Data
scannerReadQdata s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (Ptr Data)
    -- XXX Wrapping a foreign struct/union with no known destructor, leak?
    val' <- (\x -> Data <$> newForeignPtr_ x) val
    return val'

scannerReadConfig :: Scanner -> IO ScannerConfig
scannerReadConfig s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO (Ptr ScannerConfig)
    val' <- (newPtr 128 ScannerConfig) val
    return val'

scannerReadToken :: Scanner -> IO TokenType
scannerReadToken s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

scannerReadValue :: Scanner -> IO TokenValue
scannerReadValue s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO (Ptr TokenValue)
    val' <- (newPtr 8 TokenValue) val
    return val'

scannerReadLine :: Scanner -> IO Word32
scannerReadLine s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO Word32
    return val

scannerReadPosition :: Scanner -> IO Word32
scannerReadPosition s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 60) :: IO Word32
    return val

scannerReadNextToken :: Scanner -> IO TokenType
scannerReadNextToken s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

scannerReadNextValue :: Scanner -> IO TokenValue
scannerReadNextValue s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 72) :: IO (Ptr TokenValue)
    val' <- (newPtr 8 TokenValue) val
    return val'

scannerReadNextLine :: Scanner -> IO Word32
scannerReadNextLine s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 80) :: IO Word32
    return val

scannerReadNextPosition :: Scanner -> IO Word32
scannerReadNextPosition s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 84) :: IO Word32
    return val

-- XXX Skipped getter for "Scanner:msg_handler" :: Not implemented: "Wrapping foreign callbacks is not supported yet"

-- method Scanner::cur_line
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_cur_line" g_scanner_cur_line :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    IO Word32


scannerCurLine ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    m Word32
scannerCurLine _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_scanner_cur_line _obj'
    touchManagedPtr _obj
    return result

-- method Scanner::cur_position
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_cur_position" g_scanner_cur_position :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    IO Word32


scannerCurPosition ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    m Word32
scannerCurPosition _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_scanner_cur_position _obj'
    touchManagedPtr _obj
    return result

-- method Scanner::cur_token
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "TokenType"
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_cur_token" g_scanner_cur_token :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    IO CUInt


scannerCurToken ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    m TokenType
scannerCurToken _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_scanner_cur_token _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method Scanner::destroy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_destroy" g_scanner_destroy :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    IO ()


scannerDestroy ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    m ()
scannerDestroy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    g_scanner_destroy _obj'
    touchManagedPtr _obj
    return ()

-- method Scanner::eof
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_eof" g_scanner_eof :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    IO CInt


scannerEof ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    m Bool
scannerEof _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_scanner_eof _obj'
    let result' = (/= 0) result
    touchManagedPtr _obj
    return result'

-- method Scanner::get_next_token
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "TokenType"
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_get_next_token" g_scanner_get_next_token :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    IO CUInt


scannerGetNextToken ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    m TokenType
scannerGetNextToken _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_scanner_get_next_token _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method Scanner::input_file
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "input_fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "input_fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_input_file" g_scanner_input_file :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    Int32 ->                                -- input_fd : TBasicType TInt32
    IO ()


scannerInputFile ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    Int32 ->                                -- input_fd
    m ()
scannerInputFile _obj input_fd = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    g_scanner_input_file _obj' input_fd
    touchManagedPtr _obj
    return ()

-- method Scanner::input_text
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "text_len", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "text_len", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_input_text" g_scanner_input_text :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    CString ->                              -- text : TBasicType TUTF8
    Word32 ->                               -- text_len : TBasicType TUInt32
    IO ()


scannerInputText ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    T.Text ->                               -- text
    Word32 ->                               -- text_len
    m ()
scannerInputText _obj text text_len = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    text' <- textToCString text
    g_scanner_input_text _obj' text' text_len
    touchManagedPtr _obj
    freeMem text'
    return ()

-- method Scanner::peek_next_token
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "TokenType"
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_peek_next_token" g_scanner_peek_next_token :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    IO CUInt


scannerPeekNextToken ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    m TokenType
scannerPeekNextToken _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_scanner_peek_next_token _obj'
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr _obj
    return result'

-- method Scanner::scope_add_symbol
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scope_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "symbol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scope_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "symbol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_scope_add_symbol" g_scanner_scope_add_symbol :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    Word32 ->                               -- scope_id : TBasicType TUInt32
    CString ->                              -- symbol : TBasicType TUTF8
    Ptr () ->                               -- value : TBasicType TVoid
    IO ()


scannerScopeAddSymbol ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    Word32 ->                               -- scope_id
    T.Text ->                               -- symbol
    Ptr () ->                               -- value
    m ()
scannerScopeAddSymbol _obj scope_id symbol value = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    symbol' <- textToCString symbol
    g_scanner_scope_add_symbol _obj' scope_id symbol' value
    touchManagedPtr _obj
    freeMem symbol'
    return ()

-- method Scanner::scope_remove_symbol
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scope_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "symbol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scope_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "symbol", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_scope_remove_symbol" g_scanner_scope_remove_symbol :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    Word32 ->                               -- scope_id : TBasicType TUInt32
    CString ->                              -- symbol : TBasicType TUTF8
    IO ()


scannerScopeRemoveSymbol ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    Word32 ->                               -- scope_id
    T.Text ->                               -- symbol
    m ()
scannerScopeRemoveSymbol _obj scope_id symbol = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    symbol' <- textToCString symbol
    g_scanner_scope_remove_symbol _obj' scope_id symbol'
    touchManagedPtr _obj
    freeMem symbol'
    return ()

-- method Scanner::set_scope
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scope_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scope_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_set_scope" g_scanner_set_scope :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    Word32 ->                               -- scope_id : TBasicType TUInt32
    IO Word32


scannerSetScope ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    Word32 ->                               -- scope_id
    m Word32
scannerSetScope _obj scope_id = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_scanner_set_scope _obj' scope_id
    touchManagedPtr _obj
    return result

-- method Scanner::sync_file_offset
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_sync_file_offset" g_scanner_sync_file_offset :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    IO ()


scannerSyncFileOffset ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    m ()
scannerSyncFileOffset _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    g_scanner_sync_file_offset _obj'
    touchManagedPtr _obj
    return ()

-- method Scanner::unexp_token
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expected_token", argType = TInterface "GLib" "TokenType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "identifier_spec", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "symbol_spec", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "symbol_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_error", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "GLib" "Scanner", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expected_token", argType = TInterface "GLib" "TokenType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "identifier_spec", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "symbol_spec", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "symbol_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "is_error", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_scanner_unexp_token" g_scanner_unexp_token :: 
    Ptr Scanner ->                          -- _obj : TInterface "GLib" "Scanner"
    CUInt ->                                -- expected_token : TInterface "GLib" "TokenType"
    CString ->                              -- identifier_spec : TBasicType TUTF8
    CString ->                              -- symbol_spec : TBasicType TUTF8
    CString ->                              -- symbol_name : TBasicType TUTF8
    CString ->                              -- message : TBasicType TUTF8
    Int32 ->                                -- is_error : TBasicType TInt32
    IO ()


scannerUnexpToken ::
    (MonadIO m) =>
    Scanner ->                              -- _obj
    TokenType ->                            -- expected_token
    T.Text ->                               -- identifier_spec
    T.Text ->                               -- symbol_spec
    T.Text ->                               -- symbol_name
    T.Text ->                               -- message
    Int32 ->                                -- is_error
    m ()
scannerUnexpToken _obj expected_token identifier_spec symbol_spec symbol_name message is_error = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let expected_token' = (fromIntegral . fromEnum) expected_token
    identifier_spec' <- textToCString identifier_spec
    symbol_spec' <- textToCString symbol_spec
    symbol_name' <- textToCString symbol_name
    message' <- textToCString message
    g_scanner_unexp_token _obj' expected_token' identifier_spec' symbol_spec' symbol_name' message' is_error
    touchManagedPtr _obj
    freeMem identifier_spec'
    freeMem symbol_spec'
    freeMem symbol_name'
    freeMem message'
    return ()