On this page:
1.1 Creating a Lexer
lexer
lexer-src-pos
start-pos
end-pos
lexeme
input-port
return-without-pos
position
position-token
file-path
1.2 Lexer Abbreviations and Macros
char-set
any-char
any-string
nothing
alphabetic
lower-case
upper-case
title-case
numeric
symbolic
punctuation
graphic
whitespace
blank
iso-control
define-lex-abbrev
define-lex-abbrevs
define-lex-trans
1.3 Lexer SRE Operators
*
+
?
=
>=
**
or
:
seq
&
-
~
/
1.4 Lexer Legacy Operators
epsilon
~
1.5 Tokens
define-tokens
define-empty-tokens
token-name
token-value
token?

1 Lexers🔗ℹ

 (require parser-tools/lex) package: parser-tools-lib

1.1 Creating a Lexer🔗ℹ

syntax

(lexer maybe-suppress-warnings [trigger action-expr] ...)

 
maybe-suppress-warnings = 
  | #:suppress-warnings
     
trigger = re
  | (eof)
  | (special)
  | (special-comment)
     
re = id
  | string
  | character
  | (repetition lo hi re)
  | (union re ...)
  | (intersection re ...)
  | (complement re)
  | (concatenation re ...)
  | (char-range char char)
  | (char-complement re)
  | (id datum ...)
Produces a function that takes an input-port, matches the re patterns against the buffer, and returns the result of executing the corresponding action-expr. When multiple patterns match, a lexer will choose the longest match, breaking ties in favor of the rule appearing first.

The implementation of syntax-color/racket-lexer contains a lexer for the racket language. In addition, files in the "examples" sub-directory of the "parser-tools" collection contain simpler example lexers.

An re is matched as follows:

Note that both (concatenation) and "" match the empty string, (union) matches nothing, (intersection) matches any string, and (char-complement (union)) matches any single character.

The regular expression language is not designed to be used directly, but rather as a basis for a user-friendly notation written with regular expression macros. For example, parser-tools/lex-sre supplies operators from Olin Shivers’s SREs, and parser-tools/lex-plt-v200 supplies (deprecated) operators from the previous version of this library. Since those libraries provide operators whose names match other Racket bindings, such as * and +, they normally must be imported using a prefix:

(require (prefix-in : parser-tools/lex-sre))

The suggested prefix is :, so that :* and :+ are imported. Of course, a prefix other than : (such as re-) will work too.

Since negation is not a common operator on regular expressions, here are a few examples, using : prefixed SRE syntax:

The start-pos, end-pos, lexeme, input-port, and return-without-pos forms have special meaning inside of a lexer.

The lexer raises an exception (exn:read) if none of the regular expressions match the input. Hint: If (any-char custom-error-behavior) is the last rule, then there will always be a match, and custom-error-behavior is executed to handle the error situation as desired, only consuming the first character from the input buffer.

In addition to returning characters, input ports can return eof-objects. Custom input ports can also return a special-comment value to indicate a non-textual comment, or return another arbitrary value (a special). The non-re trigger forms handle these cases:

End-of-files, specials, special-comments and special-errors cannot be parsed via a rule using an ordinary regular expression (but dropping down and manipulating the port to handle them is possible in some situations).

Since the lexer gets its source information from the port, use port-count-lines! to enable the tracking of line and column information. Otherwise, the line and column information will return #f.

When peeking from the input port raises an exception (such as by an embedded XML editor with malformed syntax), the exception can be raised before all tokens preceding the exception have been returned.

Each time the racket code for a lexer is compiled (e.g. when a ".rkt" file containing a lexer form is loaded), the lexer generator is run. To avoid this overhead place the lexer into a module and compile the module to a ".zo" bytecode file.

If the lexer can accept the empty string, a message is sent to current-logger. These warnings can be disabled by giving the #:suppress-warnings flag.

Examples:
> (define sample-input "( lambda (a ) (add_number a 42  ))")
; A function that partially tokenizes the sample input data
> (define (get-tokens a-lexer)
    (define p (open-input-string sample-input))
    (list (a-lexer p)
          (a-lexer p)
          (a-lexer p)
          (a-lexer p)
          (a-lexer p)))
; A lexer that uses primitive operations directly
> (define the-lexer/primitive
    (lexer
      [(eof) eof]
      ["(" 'left-paren]
      [")" 'right-paren]
      [(repetition 1 +inf.0 numeric) (string->number lexeme)]
      [(concatenation (union alphabetic #\_)
                      (repetition 0 +inf.0 (union alphabetic numeric #\_)))
       lexeme]
      ; invoke the lexer again to skip the current token
      [whitespace (the-lexer/primitive input-port)]))
> (get-tokens the-lexer/primitive)

'(left-paren "lambda" left-paren "a" right-paren)

; Another lexer that uses SRE operators but has the same functionality
> (require (prefix-in : parser-tools/lex-sre))
> (define the-lexer/SRE
    (lexer
      [(eof) eof]
      ["(" 'left-paren]
      [")" 'right-paren]
      [(:+ numeric) (string->number lexeme)]
      [(:: (:or alphabetic #\_) (:* (:or alphabetic numeric #\_)))
       lexeme]
      [whitespace (the-lexer/SRE input-port)]))
> (get-tokens the-lexer/SRE)

'(left-paren "lambda" left-paren "a" right-paren)

Changed in version 7.7.0.7 of package parser-tools-lib: Add #:suppress-warnings flag.

syntax

(lexer-src-pos maybe-suppress-warnings [trigger action-expr] ...)

Like lexer, but for each action-result produced by an action-expr, returns (make-position-token action-result start-pos end-pos) instead of simply action-result.

syntax

start-pos

Produces a position struct for the first character matched. Its use outside of a lexer action is a syntax error.

syntax

end-pos

Produces a position struct for the character after the last character in the match. Its use outside of a lexer action is a syntax error.

syntax

lexeme

Produces the matched string. Its use outside of a lexer action is a syntax error.

Produces the input port being processed, which is particularly useful for matching input with multiple lexers. Its use outside of a lexer action is a syntax error.

Produces a function (continuation) that immediately returns its argument from the lexer. This is useful in lexer-src-pos to prevent the lexer from adding source information. For example:
(define get-token
  (lexer-src-pos
    ...
    [(comment) (get-token input-port)]
    ...))
would wrap the source location information for the comment around the value of the recursive call. Using [(comment) (return-without-pos (get-token input-port))] will cause the value of the recursive call to be returned without wrapping position around it. Its use outside of a lexer action is a syntax error.

struct

(struct position (offset line col)
    #:extra-constructor-name make-position)
  offset : exact-positive-integer?
  line : exact-positive-integer?
  col : exact-nonnegative-integer?
Instances of position are bound to start-pos and end-pos. The offset field contains the offset of the character in the input. The line field contains the line number of the character. The col field contains the offset in the current line. The fields are indexed as in the position-counting of ports.

struct

(struct position-token (token start-pos end-pos)
    #:extra-constructor-name make-position-token)
  token : any/c
  start-pos : position?
  end-pos : position?
Lexers created with lexer-src-pos return instances of position-token.

parameter

(file-path)  any/c

(file-path source)  void?
  source : any/c
A parameter that the lexer uses as the source location if it raises a exn:fail:read error. Setting this parameter allows DrRacket, for example, to open the file containing the error.

1.2 Lexer Abbreviations and Macros🔗ℹ

syntax

(char-set string)

A lexer macro that matches any character in string.

syntax

any-char

A lexer abbreviation that matches any character.

A lexer abbreviation that matches any string.

syntax

nothing

A lexer abbreviation that matches no string.

syntax

alphabetic

syntax

lower-case

syntax

upper-case

syntax

title-case

syntax

numeric

syntax

symbolic

syntax

punctuation

syntax

graphic

syntax

whitespace

syntax

blank

syntax

iso-control

Lexer abbreviations that match char-alphabetic? characters, char-lower-case? characters, etc.

syntax

(define-lex-abbrev id re)

Defines a lexer abbreviation by associating a regular expression to be used in place of the id in other regular expression. The definition of name has the same scoping properties as a other syntactic binding (e.g., it can be exported from a module).

syntax

(define-lex-abbrevs (id re) ...)

Like define-lex-abbrev, but defines several lexer abbreviations.

syntax

(define-lex-trans id trans-expr)

Defines a lexer macro, where trans-expr produces a transformer procedure that takes one argument. When (id datum ...) appears as a regular expression, it is replaced with the result of applying the transformer to the expression.

1.3 Lexer SRE Operators🔗ℹ

 (require parser-tools/lex-sre) package: parser-tools-lib

syntax

(* re ...)

Repetition of re sequence 0 or more times.

syntax

(+ re ...)

Repetition of re sequence 1 or more times.

syntax

(? re ...)

Zero or one occurrence of re sequence.

syntax

(= n re ...)

Exactly n occurrences of re sequence, where n must be a literal exact, non-negative number.

syntax

(>= n re ...)

At least n occurrences of re sequence, where n must be a literal exact, non-negative number.

syntax

(** n m re ...)

Between n and m (inclusive) occurrences of re sequence, where n must be a literal exact, non-negative number, and m must be literally either #f, +inf.0, or an exact, non-negative number; a #f value for m is the same as +inf.0.

syntax

(or re ...)

Same as (union re ...).

syntax

(: re ...)

syntax

(seq re ...)

Both forms concatenate the res.

syntax

(& re ...)

Intersects the res.

syntax

(- re ...)

The set difference of the res.

syntax

(~ re ...)

Character-set complement, which each re must match exactly one character.

syntax

(/ char-or-string ...)

Character ranges, matching characters between successive pairs of characters.

1.4 Lexer Legacy Operators🔗ℹ

 (require parser-tools/lex-plt-v200)
  package: parser-tools-lib

The parser-tools/lex-plt-v200 module re-exports *, +, ?, and & from parser-tools/lex-sre. It also re-exports :or as :, :: as @, :~ as ^, and :/ as -.

syntax

(epsilon)

A lexer macro that matches an empty sequence.

syntax

(~ re ...)

The same as (complement re ...).

1.5 Tokens🔗ℹ

Each action-expr in a lexer form can produce any kind of value, but for many purposes, producing a token value is useful. Tokens are usually necessary for inter-operating with a parser generated by parser-tools/yacc or parser-tools/cfg-parser, but tokens may not be the right choice when using lexer in other situations.

Examples:
> (define-tokens basic-tokens (NUM ID))
> (define-empty-tokens punct-tokens (LPAREN RPAREN EOF))
> (define the-lexer/tokens
    (lexer
      [(eof) (token-EOF)]
      ["(" (token-LPAREN)]
      [")" (token-RPAREN)]
      [(:+ numeric) (token-NUM (string->number lexeme))]
      [(:: (:or alphabetic #\_)
           (:* (:or alphabetic numeric #\_)))
       (token-ID (string->symbol lexeme))]
      [whitespace (the-lexer/tokens input-port)]))
; Use get-tokens defined in Creating a Lexer
> (get-tokens the-lexer/tokens)

(list 'LPAREN (token 'ID 'lambda) 'LPAREN (token 'ID 'a) 'RPAREN)

syntax

(define-tokens group-id (token-id ...))

Binds group-id to the group of tokens being defined. For each token-id, a function token-token-id is created that takes any value and puts it in a token record specific to token-id. A token can be inspected using token-name and token-value.

A token cannot be named error, since error has a special use in the parser.

syntax

(define-empty-tokens group-id (token-id ...))

Like define-tokens, but each token constructor token-token-id takes no arguments and returns (quote token-id).

procedure

(token-name t)  symbol?

  t : (or/c token? symbol?)
Returns the name of a token that is represented either by a symbol or a token structure.

procedure

(token-value t)  any/c

  t : (or/c token? symbol?)
Returns the value of a token that is represented either by a symbol or a token structure, returning #f for a symbol token.

procedure

(token? v)  boolean?

  v : any/c
Returns #t if val is a token structure, #f otherwise.