gi-glib-2.0.23: GLib bindings
CopyrightWill Thompson Iñaki García Etxebarria and Jonas Platte
LicenseLGPL-2.1
MaintainerIñaki García Etxebarria
Safe HaskellNone
LanguageHaskell2010

GI.GLib.Structs.Scanner

Description

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 ScannerMsgFunc.

Synopsis

Exported types

newtype Scanner Source #

Memory-managed wrapper type.

Constructors

Scanner (ManagedPtr Scanner) 

Instances

Instances details
Eq Scanner Source # 
Instance details

Defined in GI.GLib.Structs.Scanner

Methods

(==) :: Scanner -> Scanner -> Bool #

(/=) :: Scanner -> Scanner -> Bool #

WrappedPtr Scanner Source # 
Instance details

Defined in GI.GLib.Structs.Scanner

tag ~ 'AttrSet => Constructible Scanner tag Source # 
Instance details

Defined in GI.GLib.Structs.Scanner

Methods

new :: MonadIO m => (ManagedPtr Scanner -> Scanner) -> [AttrOp Scanner tag] -> m Scanner #

newZeroScanner :: MonadIO m => m Scanner Source #

Construct a Scanner struct initialized to zero.

noScanner :: Maybe Scanner Source #

A convenience alias for Nothing :: Maybe Scanner.

Methods

Overloaded methods

curLine

scannerCurLine Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> m Word32

Returns: the current line

Returns the current line in the input stream (counting from 1). This is the line of the last token parsed via scannerGetNextToken.

curPosition

scannerCurPosition Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> m Word32

Returns: the current position on the line

Returns the current position in the current line (counting from 0). This is the position of the last token parsed via scannerGetNextToken.

curToken

scannerCurToken Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> m TokenType

Returns: the current token type

Gets the current token type. This is simply the token field in the Scanner structure.

destroy

scannerDestroy Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> m () 

Frees all memory used by the Scanner.

eof

scannerEof Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> m Bool

Returns: True if the scanner has reached the end of the file or text buffer

Returns True if the scanner has reached the end of the file or text buffer.

getNextToken

scannerGetNextToken Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> m TokenType

Returns: the type of the token

Parses the next token just like scannerPeekNextToken and also removes it from the input stream. The token data is placed in the token, value, line, and position fields of the Scanner structure.

inputFile

scannerInputFile Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> Int32

inputFd: a file descriptor

-> m () 

Prepares to scan a file.

inputText

scannerInputText Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> Text

text: the text buffer to scan

-> Word32

textLen: the length of the text buffer

-> m () 

Prepares to scan a text buffer.

lookupSymbol

scannerLookupSymbol Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> 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

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.

peekNextToken

scannerPeekNextToken Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> m TokenType

Returns: the type of the token

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 Scanner structure.

Note that, while the token is not removed from the input stream (i.e. the next call to 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.

scopeAddSymbol

scannerScopeAddSymbol Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> Word32

scopeId: the scope id

-> Text

symbol: the symbol to add

-> Ptr ()

value: the value of the symbol

-> m () 

Adds a symbol to the given scope.

scopeLookupSymbol

scannerScopeLookupSymbol Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> Word32

scopeId: the scope id

-> 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.

Looks up a symbol in a scope and return its value. If the symbol is not bound in the scope, Nothing is returned.

scopeRemoveSymbol

scannerScopeRemoveSymbol Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> Word32

scopeId: the scope id

-> Text

symbol: the symbol to remove

-> m () 

Removes a symbol from a scope.

setScope

scannerSetScope Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> Word32

scopeId: the new scope id

-> m Word32

Returns: the old scope id

Sets the current scope.

syncFileOffset

scannerSyncFileOffset Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> m () 

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.

unexpToken

scannerUnexpToken Source #

Arguments

:: (HasCallStack, MonadIO m) 
=> Scanner

scanner: a Scanner

-> TokenType

expectedToken: the expected token

-> Text

identifierSpec: a string describing how the scanner's user refers to identifiers (Nothing defaults to "identifier"). This is used if expectedToken is TokenTypeIdentifier or TokenTypeIdentifierNull.

-> Text

symbolSpec: a string describing how the scanner's user refers to symbols (Nothing defaults to "symbol"). This is used if expectedToken is TokenTypeSymbol or any token value greater than G_TOKEN_LAST.

-> Text

symbolName: the name of the symbol, if the scanner's current token is a symbol.

-> 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 () 

Outputs a message through the scanner's msg_handler, resulting from an unexpected token in the input stream. Note that you should not call scannerPeekNextToken followed by scannerUnexpToken without an intermediate call to scannerGetNextToken, as scannerUnexpToken evaluates the scanner's current token (not the peeked token) to construct part of the message.

Properties

config

link into the scanner configuration

clearScannerConfig :: MonadIO m => Scanner -> m () Source #

Set the value of the “config” field to Nothing. When overloading is enabled, this is equivalent to

clear #config

getScannerConfig :: MonadIO m => Scanner -> m (Maybe ScannerConfig) Source #

Get the value of the “config” field. When overloading is enabled, this is equivalent to

get scanner #config

setScannerConfig :: MonadIO m => Scanner -> Ptr ScannerConfig -> m () Source #

Set the value of the “config” field. When overloading is enabled, this is equivalent to

set scanner [ #config := value ]

inputName

name of input stream, featured by the default message handler

clearScannerInputName :: MonadIO m => Scanner -> m () Source #

Set the value of the “input_name” field to Nothing. When overloading is enabled, this is equivalent to

clear #inputName

getScannerInputName :: MonadIO m => Scanner -> m (Maybe Text) Source #

Get the value of the “input_name” field. When overloading is enabled, this is equivalent to

get scanner #inputName

setScannerInputName :: MonadIO m => Scanner -> CString -> m () Source #

Set the value of the “input_name” field. When overloading is enabled, this is equivalent to

set scanner [ #inputName := value ]

line

line number of the last token from scannerGetNextToken

getScannerLine :: MonadIO m => Scanner -> m Word32 Source #

Get the value of the “line” field. When overloading is enabled, this is equivalent to

get scanner #line

setScannerLine :: MonadIO m => Scanner -> Word32 -> m () Source #

Set the value of the “line” field. When overloading is enabled, this is equivalent to

set scanner [ #line := value ]

maxParseErrors

unused

getScannerMaxParseErrors :: MonadIO m => Scanner -> m Word32 Source #

Get the value of the “max_parse_errors” field. When overloading is enabled, this is equivalent to

get scanner #maxParseErrors

setScannerMaxParseErrors :: MonadIO m => Scanner -> Word32 -> m () Source #

Set the value of the “max_parse_errors” field. When overloading is enabled, this is equivalent to

set scanner [ #maxParseErrors := value ]

msgHandler

handler function for _warn and _error

clearScannerMsgHandler :: MonadIO m => Scanner -> m () Source #

Set the value of the “msg_handler” field to Nothing. When overloading is enabled, this is equivalent to

clear #msgHandler

getScannerMsgHandler :: MonadIO m => Scanner -> m (Maybe ScannerMsgFunc) Source #

Get the value of the “msg_handler” field. When overloading is enabled, this is equivalent to

get scanner #msgHandler

setScannerMsgHandler :: MonadIO m => Scanner -> FunPtr C_ScannerMsgFunc -> m () Source #

Set the value of the “msg_handler” field. When overloading is enabled, this is equivalent to

set scanner [ #msgHandler := value ]

nextLine

line number of the last token from scannerPeekNextToken

getScannerNextLine :: MonadIO m => Scanner -> m Word32 Source #

Get the value of the “next_line” field. When overloading is enabled, this is equivalent to

get scanner #nextLine

setScannerNextLine :: MonadIO m => Scanner -> Word32 -> m () Source #

Set the value of the “next_line” field. When overloading is enabled, this is equivalent to

set scanner [ #nextLine := value ]

nextPosition

char number of the last token from scannerPeekNextToken

getScannerNextPosition :: MonadIO m => Scanner -> m Word32 Source #

Get the value of the “next_position” field. When overloading is enabled, this is equivalent to

get scanner #nextPosition

setScannerNextPosition :: MonadIO m => Scanner -> Word32 -> m () Source #

Set the value of the “next_position” field. When overloading is enabled, this is equivalent to

set scanner [ #nextPosition := value ]

nextToken

token parsed by the last scannerPeekNextToken

getScannerNextToken :: MonadIO m => Scanner -> m TokenType Source #

Get the value of the “next_token” field. When overloading is enabled, this is equivalent to

get scanner #nextToken

setScannerNextToken :: MonadIO m => Scanner -> TokenType -> m () Source #

Set the value of the “next_token” field. When overloading is enabled, this is equivalent to

set scanner [ #nextToken := value ]

nextValue

value of the last token from scannerPeekNextToken

getScannerNextValue :: MonadIO m => Scanner -> m TokenValue Source #

Get the value of the “next_value” field. When overloading is enabled, this is equivalent to

get scanner #nextValue

parseErrors

g_scanner_error() increments this field

getScannerParseErrors :: MonadIO m => Scanner -> m Word32 Source #

Get the value of the “parse_errors” field. When overloading is enabled, this is equivalent to

get scanner #parseErrors

setScannerParseErrors :: MonadIO m => Scanner -> Word32 -> m () Source #

Set the value of the “parse_errors” field. When overloading is enabled, this is equivalent to

set scanner [ #parseErrors := value ]

position

char number of the last token from scannerGetNextToken

getScannerPosition :: MonadIO m => Scanner -> m Word32 Source #

Get the value of the “position” field. When overloading is enabled, this is equivalent to

get scanner #position

setScannerPosition :: MonadIO m => Scanner -> Word32 -> m () Source #

Set the value of the “position” field. When overloading is enabled, this is equivalent to

set scanner [ #position := value ]

qdata

quarked data

clearScannerQdata :: MonadIO m => Scanner -> m () Source #

Set the value of the “qdata” field to Nothing. When overloading is enabled, this is equivalent to

clear #qdata

getScannerQdata :: MonadIO m => Scanner -> m (Maybe Data) Source #

Get the value of the “qdata” field. When overloading is enabled, this is equivalent to

get scanner #qdata

setScannerQdata :: MonadIO m => Scanner -> Ptr Data -> m () Source #

Set the value of the “qdata” field. When overloading is enabled, this is equivalent to

set scanner [ #qdata := value ]

token

token parsed by the last scannerGetNextToken

getScannerToken :: MonadIO m => Scanner -> m TokenType Source #

Get the value of the “token” field. When overloading is enabled, this is equivalent to

get scanner #token

setScannerToken :: MonadIO m => Scanner -> TokenType -> m () Source #

Set the value of the “token” field. When overloading is enabled, this is equivalent to

set scanner [ #token := value ]

userData

unused

clearScannerUserData :: MonadIO m => Scanner -> m () Source #

Set the value of the “user_data” field to Nothing. When overloading is enabled, this is equivalent to

clear #userData

getScannerUserData :: MonadIO m => Scanner -> m (Ptr ()) Source #

Get the value of the “user_data” field. When overloading is enabled, this is equivalent to

get scanner #userData

setScannerUserData :: MonadIO m => Scanner -> Ptr () -> m () Source #

Set the value of the “user_data” field. When overloading is enabled, this is equivalent to

set scanner [ #userData := value ]

value

value of the last token from scannerGetNextToken

getScannerValue :: MonadIO m => Scanner -> m TokenValue Source #

Get the value of the “value” field. When overloading is enabled, this is equivalent to

get scanner #value