Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria (garetxe@gmail.com) |
Safe Haskell | None |
Language | Haskell2010 |
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
- newtype Scanner = Scanner (ManagedPtr Scanner)
- newZeroScanner :: MonadIO m => m Scanner
- noScanner :: Maybe Scanner
- scannerCurLine :: (HasCallStack, MonadIO m) => Scanner -> m Word32
- scannerCurPosition :: (HasCallStack, MonadIO m) => Scanner -> m Word32
- scannerCurToken :: (HasCallStack, MonadIO m) => Scanner -> m TokenType
- scannerDestroy :: (HasCallStack, MonadIO m) => Scanner -> m ()
- scannerEof :: (HasCallStack, MonadIO m) => Scanner -> m Bool
- scannerGetNextToken :: (HasCallStack, MonadIO m) => Scanner -> m TokenType
- scannerInputFile :: (HasCallStack, MonadIO m) => Scanner -> Int32 -> m ()
- scannerInputText :: (HasCallStack, MonadIO m) => Scanner -> Text -> Word32 -> m ()
- scannerLookupSymbol :: (HasCallStack, MonadIO m) => Scanner -> Text -> m (Ptr ())
- scannerPeekNextToken :: (HasCallStack, MonadIO m) => Scanner -> m TokenType
- scannerScopeAddSymbol :: (HasCallStack, MonadIO m) => Scanner -> Word32 -> Text -> Ptr () -> m ()
- scannerScopeLookupSymbol :: (HasCallStack, MonadIO m) => Scanner -> Word32 -> Text -> m (Ptr ())
- scannerScopeRemoveSymbol :: (HasCallStack, MonadIO m) => Scanner -> Word32 -> Text -> m ()
- scannerSetScope :: (HasCallStack, MonadIO m) => Scanner -> Word32 -> m Word32
- scannerSyncFileOffset :: (HasCallStack, MonadIO m) => Scanner -> m ()
- scannerUnexpToken :: (HasCallStack, MonadIO m) => Scanner -> TokenType -> Text -> Text -> Text -> Text -> Int32 -> m ()
- clearScannerConfig :: MonadIO m => Scanner -> m ()
- getScannerConfig :: MonadIO m => Scanner -> m (Maybe ScannerConfig)
- setScannerConfig :: MonadIO m => Scanner -> Ptr ScannerConfig -> m ()
- clearScannerInputName :: MonadIO m => Scanner -> m ()
- getScannerInputName :: MonadIO m => Scanner -> m (Maybe Text)
- setScannerInputName :: MonadIO m => Scanner -> CString -> m ()
- getScannerLine :: MonadIO m => Scanner -> m Word32
- setScannerLine :: MonadIO m => Scanner -> Word32 -> m ()
- getScannerMaxParseErrors :: MonadIO m => Scanner -> m Word32
- setScannerMaxParseErrors :: MonadIO m => Scanner -> Word32 -> m ()
- clearScannerMsgHandler :: MonadIO m => Scanner -> m ()
- getScannerMsgHandler :: MonadIO m => Scanner -> m (Maybe ScannerMsgFunc)
- setScannerMsgHandler :: MonadIO m => Scanner -> FunPtr C_ScannerMsgFunc -> m ()
- getScannerNextLine :: MonadIO m => Scanner -> m Word32
- setScannerNextLine :: MonadIO m => Scanner -> Word32 -> m ()
- getScannerNextPosition :: MonadIO m => Scanner -> m Word32
- setScannerNextPosition :: MonadIO m => Scanner -> Word32 -> m ()
- getScannerNextToken :: MonadIO m => Scanner -> m TokenType
- setScannerNextToken :: MonadIO m => Scanner -> TokenType -> m ()
- getScannerNextValue :: MonadIO m => Scanner -> m TokenValue
- getScannerParseErrors :: MonadIO m => Scanner -> m Word32
- setScannerParseErrors :: MonadIO m => Scanner -> Word32 -> m ()
- getScannerPosition :: MonadIO m => Scanner -> m Word32
- setScannerPosition :: MonadIO m => Scanner -> Word32 -> m ()
- clearScannerQdata :: MonadIO m => Scanner -> m ()
- getScannerQdata :: MonadIO m => Scanner -> m (Maybe Data)
- setScannerQdata :: MonadIO m => Scanner -> Ptr Data -> m ()
- getScannerToken :: MonadIO m => Scanner -> m TokenType
- setScannerToken :: MonadIO m => Scanner -> TokenType -> m ()
- clearScannerUserData :: MonadIO m => Scanner -> m ()
- getScannerUserData :: MonadIO m => Scanner -> m (Ptr ())
- setScannerUserData :: MonadIO m => Scanner -> Ptr () -> m ()
- getScannerValue :: MonadIO m => Scanner -> m TokenValue
Exported types
Memory-managed wrapper type.
Instances
WrappedPtr Scanner Source # | |
Defined in GI.GLib.Structs.Scanner | |
tag ~ AttrSet => Constructible Scanner tag Source # | |
Defined in GI.GLib.Structs.Scanner |
Methods
curLine
:: (HasCallStack, MonadIO m) | |
=> 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
:: (HasCallStack, MonadIO m) | |
=> 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
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> m TokenType | Returns: the current token type |
Gets the current token type. This is simply the token
field in the Scanner
structure.
destroy
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> m () |
Frees all memory used by the Scanner
.
eof
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> m Bool | Returns: |
Returns True
if the scanner has reached the end of
the file or text buffer.
getNextToken
:: (HasCallStack, MonadIO m) | |
=> 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
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> Int32 |
|
-> m () |
Prepares to scan a file.
inputText
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> Text |
|
-> Word32 |
|
-> m () |
Prepares to scan a text buffer.
lookupSymbol
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> Text |
|
-> m (Ptr ()) | Returns: the value of |
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
:: (HasCallStack, MonadIO m) | |
=> 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 #
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> Word32 |
|
-> Text |
|
-> Ptr () |
|
-> m () |
Adds a symbol to the given scope.
scopeLookupSymbol
scannerScopeLookupSymbol Source #
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> Word32 |
|
-> Text |
|
-> m (Ptr ()) | Returns: the value of |
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 #
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> Word32 |
|
-> Text |
|
-> m () |
Removes a symbol from a scope.
setScope
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> Word32 |
|
-> m Word32 | Returns: the old scope id |
Sets the current scope.
syncFileOffset
scannerSyncFileOffset Source #
:: (HasCallStack, MonadIO m) | |
=> 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
:: (HasCallStack, MonadIO m) | |
=> Scanner |
|
-> TokenType |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Int32 |
|
-> 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