back from fix for v209

original commit: 11670a289e951efc33133cd62de61f126510b45e
tokens
Eli Barzilay 20 years ago
parent 12687e8f0e
commit 697cf326b4

@ -3,140 +3,227 @@
;; Provides the syntax used to create lexers and the functions needed to ;; Provides the syntax used to create lexers and the functions needed to
;; create and use the buffer that the lexer reads from. See doc.txt. ;; create and use the buffer that the lexer reads from. See doc.txt.
(require-for-syntax "private-lex/util.ss" (require-for-syntax (lib "list.ss")
(lib "stx.ss" "syntax")
(lib "define.ss" "syntax")
(lib "boundmap.ss" "syntax")
"private-lex/util.ss"
"private-lex/actions.ss" "private-lex/actions.ss"
"private-lex/front.ss") "private-lex/front.ss"
"private-lex/unicode-chars.ss")
(require (lib "readerr.ss" "syntax") (require (lib "stxparam.ss")
(lib "cffi.ss" "compiler") (lib "readerr.ss" "syntax")
"private-lex/token.ss") "private-lex/token.ss")
(provide lexer lexer-src-pos define-lex-abbrev define-lex-abbrevs (provide lexer lexer-src-pos define-lex-abbrev define-lex-abbrevs define-lex-trans
get-position position-offset position-line position-col position?
define-tokens define-empty-tokens token-name token-value token? file-path) ;; Dealing with tokens and related structures
define-tokens define-empty-tokens token-name token-value token?
(define file-path (make-parameter #f)) (struct position (offset line col))
(struct position-token (token start-pos end-pos))
;; File path for highlighting errors while lexing
file-path
;; Lex abbrevs for unicode char sets. See mzscheme manual section 3.4.
any-char any-string nothing alphabetic lower-case upper-case title-case
numeric symbolic punctuation graphic whitespace blank iso-control
;; A regular expression operator
char-set)
(define-syntaxes (lexer lexer-src-pos) ;; wrap-action: syntax-object src-pos? -> syntax-object
(let ((build-lexer (define-for-syntax (wrap-action action src-pos?)
(lambda (wrap?) (with-syntax ((action-stx
(lambda (stx) (if src-pos?
(syntax-case stx () #`(let/ec ret
((_) (syntax-parameterize
(raise-syntax-error #f "empty lexer is not allowed" stx)) ((return-without-pos (make-rename-transformer #'ret)))
((_ re-act ...) (make-position-token #,action start-pos end-pos)))
(begin action)))
(for-each (syntax/loc action
(lambda (x) (lambda (start-pos-p end-pos-p lexeme-p input-port-p)
(syntax-case x () (syntax-parameterize
((re act) (void)) ((start-pos (make-rename-transformer #'start-pos-p))
(_ (raise-syntax-error 'lexer (end-pos (make-rename-transformer #'end-pos-p))
"expects regular expression / action pairs" (lexeme (make-rename-transformer #'lexeme-p))
x)))) (input-port (make-rename-transformer #'input-port-p)))
(syntax->list (syntax (re-act ...)))) action-stx)))))
(let* ((spec/re-act-lst
(syntax->list (syntax (re-act ...)))) (define-for-syntax (make-lexer-trans src-pos?)
(eof-act (lambda (stx)
(get-special-action spec/re-act-lst 'eof #''eof)) (syntax-case stx ()
(spec-act ((_)
(get-special-action spec/re-act-lst 'special #'(void))) (raise-syntax-error #f "accepts the empty string" stx))
(spec-error-act ((_ re-act ...)
(get-special-action spec/re-act-lst 'special-error #'(raise exception))) (begin
(spec-comment-act (for-each
(get-special-action spec/re-act-lst 'special-comment #'#f)) (lambda (x)
(re-act-lst (syntax-case x ()
(filter-out-specials spec/re-act-lst ((re act) (void))
'(special special-comment special-error eof)))) (_ (raise-syntax-error #f
(let-values (((trans start actions no-look) "not a regular expression / action pair"
(build-lexer re-act-lst))) stx
(with-syntax ((start-state-stx start) x))))
(trans-table-stx trans) (syntax->list (syntax (re-act ...))))
(no-lookahead-stx no-look) (let* ((spec/re-act-lst
(actions-stx `(vector ,@(map (lambda (a) (syntax->list (syntax (re-act ...))))
(if a (wrap-action a 'lexeme #'here a) #f)) (eof-act
(vector->list actions)))) (get-special-action spec/re-act-lst #'eof #''eof))
(spec-act-stx (spec-act
(wrap-action spec-act 'special #'here spec-act)) (get-special-action spec/re-act-lst #'special #'(void)))
(spec-error-act-stx (spec-error-act
(wrap-action spec-error-act 'exception #'here spec-error-act)) (get-special-action spec/re-act-lst #'special-error #'(raise lexeme)))
(has-comment-act?-stx (if (syntax-e spec-comment-act) #t #f)) (spec-comment-act
(spec-comment-act-stx (get-special-action spec/re-act-lst #'special-comment #'#f))
(wrap-action spec-comment-act (gensym) #'here spec-comment-act)) (ids (list #'special #'special-comment #'special-error #'eof))
(eof-act-stx (re-act-lst
(wrap-action eof-act 'lexeme #'here eof-act)) (filter
(wrap? wrap?)) (lambda (spec/re-act)
(syntax (syntax-case spec/re-act ()
(lexer-body start-state-stx (((special) act)
trans-table-stx (not (ormap
actions-stx (lambda (x)
no-lookahead-stx (module-or-top-identifier=? (syntax special) x))
spec-act-stx ids)))
spec-error-act-stx (_ #t)))
has-comment-act?-stx spec/re-act-lst))
spec-comment-act-stx (name-lst (map (lambda (x) (datum->syntax-object #f (gensym))) re-act-lst))
eof-act-stx (act-lst (map (lambda (x) (stx-car (stx-cdr x))) re-act-lst))
wrap?)))))))))))) (re-actname-lst (map (lambda (re-act name)
(values (list (stx-car re-act)
(build-lexer #f) name))
(build-lexer #t)))) re-act-lst
name-lst)))
(let-values (((trans start action-names no-look disappeared-uses)
(build-lexer re-actname-lst)))
#;(when (vector-ref action-names start)
(raise-syntax-error #f "accepts the empty string" stx))
(with-syntax ((start-state-stx start)
(trans-table-stx trans)
(no-lookahead-stx no-look)
((name ...) name-lst)
((act ...) (map (lambda (a)
(wrap-action a src-pos?))
act-lst))
((act-name ...) (vector->list action-names))
(spec-act-stx
(wrap-action spec-act src-pos?))
(spec-error-act-stx
(wrap-action spec-error-act src-pos?))
(has-comment-act?-stx
(if (syntax-e spec-comment-act) #t #f))
(spec-comment-act-stx
(wrap-action spec-comment-act src-pos?))
(eof-act-stx (wrap-action eof-act src-pos?)))
(syntax-property
(syntax/loc stx
(let ([name act] ...)
(lexer-body start-state-stx
trans-table-stx
(vector act-name ...)
no-lookahead-stx
spec-act-stx
spec-error-act-stx
has-comment-act?-stx
spec-comment-act-stx
eof-act-stx)))
'disappeared-use
disappeared-uses)))))))))
(define-syntax lexer (make-lexer-trans #f))
(define-syntax lexer-src-pos (make-lexer-trans #t))
(define-syntax (define-lex-abbrev stx) (define-syntax (define-lex-abbrev stx)
(syntax-case stx () (syntax-case stx ()
((_ name re) ((_ name re)
(syntax (identifier? (syntax name))
(syntax/loc stx
(define-syntax name (define-syntax name
(make-lex-abbrev (quote-syntax re))))) (make-lex-abbrev (quote-syntax re)))))
(_ (_
(raise-syntax-error (raise-syntax-error
#f #f
"Form should be (define-lex-abbrev name re)" "form should be (define-lex-abbrev name re)"
stx)))) stx))))
(define-syntax (define-lex-abbrevs stx) (define-syntax (define-lex-abbrevs stx)
(syntax-case stx () (syntax-case stx ()
((_ x ...) ((_ x ...)
(let* ((abbrev (syntax->list (syntax (x ...)))) (with-syntax (((abbrev ...)
(r (map (lambda (a) (map
(syntax-case a () (lambda (a)
((name re) (syntax-case a ()
(identifier? (syntax name)) ((name re)
(syntax (define-lex-abbrev name re))) (identifier? (syntax name))
(_ (raise-syntax-error (syntax/loc a (define-lex-abbrev name re)))
'Lexer-abbreviation (_ (raise-syntax-error
"Form should be (identifier value)" #f
a)))) "form should be (define-lex-abbrevs (name re) ...)"
abbrev))) stx
(datum->syntax-object a))))
#'here (syntax->list (syntax (x ...))))))
(cons 'begin r) (syntax/loc stx (begin abbrev ...))))
stx))) (_
(raise-syntax-error
#f
"form should be (define-lex-abbrevs (name re) ...)"
stx))))
(define-syntax (define-lex-trans stx)
(syntax-case stx ()
((_ name-form body-form)
(let-values (((name body)
(normalize-definition (syntax (define-syntax name-form body-form)) #'lambda)))
#`(define-syntax #,name
(let ((certifier (syntax-local-certifier)))
(make-lex-trans (lambda (stx)
(certifier (#,body stx) 'a)))))))
(_ (_
(raise-syntax-error (raise-syntax-error
#f #f
"Form should be (define-lex-abbrevs (name re) ...)" "form should be (define-lex-trans name transformer)"
stx)))) stx))))
(define (get-next-state-helper char min max table)
(if (>= min max)
#f
(let* ((try (quotient (+ min max) 2))
(el (vector-ref table try))
(r1 (vector-ref el 0))
(r2 (vector-ref el 1)))
(cond
((and (>= char r1) (<= char r2)) (vector-ref el 2))
((< char r1) (get-next-state-helper char min try table))
(else (get-next-state-helper char (add1 try) max table))))))
(define (get-next-state char table)
(if table
(get-next-state-helper char 0 (vector-length table) table)
#f))
(define (lexer-body start-state trans-table actions no-lookahead (define (lexer-body start-state trans-table actions no-lookahead
special-action special-error-action special-action special-error-action
has-special-comment-action? special-comment-action eof-action wrap?) has-special-comment-action? special-comment-action eof-action)
(letrec ((lexer (letrec ((lexer
(lambda (ip) (lambda (ip)
(unless (input-port? ip)
(raise-type-error
'lexer
"input-port"
0
ip))
(let ((first-pos (get-position ip)) (let ((first-pos (get-position ip))
(first-char (peek-char-or-special ip 0))) (first-char (peek-char-or-special ip 0)))
;(printf "(peek-char-or-special port 0) = ~e~n" first-char)
(cond (cond
((eq? 'special first-char) ((eof-object? first-char)
(do-match ip first-pos eof-action (read-char-or-special ip)))
((not (char? first-char))
(let* ((comment? #f) (let* ((comment? #f)
(error? #f) (error? #f)
(spec (with-handlers ((exn:special-comment? (spec (with-handlers ((special-comment?
(lambda (x) (set! comment? #t))) (lambda (x) (set! comment? #t)))
(not-break-exn? (exn:fail?
(lambda (ex) (set! error? #t) ex))) (lambda (ex) (set! error? #t) ex)))
(read-char-or-special ip)))) (read-char-or-special ip))))
(cond (cond
@ -147,9 +234,7 @@
(comment? special-comment-action) (comment? special-comment-action)
(error? special-error-action) (error? special-error-action)
(else special-action)) (else special-action))
spec wrap?))))) spec)))))
((eof-object? first-char)
(do-match ip first-pos eof-action (read-char-or-special ip) wrap?))
(else (else
(let lexer-loop ( (let lexer-loop (
;; current-state ;; current-state
@ -160,47 +245,56 @@
;; including a match at the current state ;; including a match at the current state
(longest-match-action (longest-match-action
(vector-ref actions start-state)) (vector-ref actions start-state))
;; how many bytes preceed char
(length-bytes 0)
;; how many characters have been read ;; how many characters have been read
;; including the one just read ;; including the one just read
(length 1) (length-chars 1)
;; how many characters are in the longest match ;; how many characters are in the longest match
(longest-match-length 0)) (longest-match-length 0))
(let ((next-state (let ((next-state
(cond (cond
((eof-object? char) #f) ((eof-object? char) #f)
((eq? char 'special) #f) ((not (char? char)) #f)
(else (else (get-next-state (char->integer char)
(vector-ref (vector-ref trans-table state))))))
trans-table
(+ (char->integer char) (* 256 state)))))))
(cond (cond
((not next-state) ((not next-state)
(check-match ip first-pos longest-match-length (check-match ip first-pos longest-match-length
length longest-match-action wrap?)) length-chars longest-match-action))
((vector-ref no-lookahead next-state) ((vector-ref no-lookahead next-state)
(let ((act (vector-ref actions next-state))) (let ((act (vector-ref actions next-state)))
(check-match ip (check-match ip
first-pos first-pos
(if act length longest-match-length) (if act length-chars longest-match-length)
length length-chars
(if act act longest-match-action) (if act act longest-match-action))))
wrap?)))
(else (else
(let ((act (vector-ref actions next-state))) (let* ((act (vector-ref actions next-state))
(next-length-bytes (+ (char-utf-8-length char) length-bytes))
(next-char (peek-char-or-special ip next-length-bytes)))
#;(printf "(peek-char-or-special port ~e) = ~e~n"
next-length-bytes next-char)
(lexer-loop next-state (lexer-loop next-state
(peek-char-or-special ip length) next-char
(if act (if act
act act
longest-match-action) longest-match-action)
(add1 length) next-length-bytes
(add1 length-chars)
(if act (if act
length length-chars
longest-match-length))))))))))))) longest-match-length)))))))))))))
lexer)) (lambda (ip)
(unless (input-port? ip)
(raise-type-error
'lexer
"input-port"
0
ip))
(lexer ip))))
(define id (lambda (x) x)) (define (check-match lb first-pos longest-match-length length longest-match-action)
(define (check-match lb first-pos longest-match-length length longest-match-action wrap?)
(unless longest-match-action (unless longest-match-action
(let* ((match (read-string length lb)) (let* ((match (read-string length lb))
(end-pos (get-position lb))) (end-pos (get-position lb)))
@ -212,23 +306,81 @@
(position-offset first-pos) (position-offset first-pos)
(- (position-offset end-pos) (position-offset first-pos))))) (- (position-offset end-pos) (position-offset first-pos)))))
(let ((match (read-string longest-match-length lb))) (let ((match (read-string longest-match-length lb)))
(do-match lb first-pos longest-match-action match wrap?))) ;(printf "(read-string ~e port) = ~e~n" longest-match-length match)
(do-match lb first-pos longest-match-action match)))
(define (do-match ip first-pos action value wrap?) (define file-path (make-parameter #f))
(let ((end-pos (get-position ip)))
(cond (define (do-match ip first-pos action value)
(wrap? #;(printf "(action ~a ~a ~a ~a)~n"
(let/ec ret (position-offset first-pos) (position-offset (get-position ip)) value ip)
(list (action first-pos end-pos value ret ip) (action first-pos (get-position ip) value ip))
first-pos
end-pos)))
(else
(action first-pos end-pos value id ip)))))
(define-struct position (offset line col))
(define (get-position ip) (define (get-position ip)
(let-values (((line col off) (port-next-location ip))) (let-values (((line col off) (port-next-location ip)))
(make-position off line col))) (make-position off line col)))
(define-syntax (create-unicode-abbrevs stx)
(syntax-case stx ()
((_ ctxt)
(with-syntax (((ranges ...) (map (lambda (range)
`(union ,@(map (lambda (x)
`(char-range ,(integer->char (car x))
,(integer->char (cdr x))))
range)))
(list (force alphabetic-ranges)
(force lower-case-ranges)
(force upper-case-ranges)
(force title-case-ranges)
(force numeric-ranges)
(force symbolic-ranges)
(force punctuation-ranges)
(force graphic-ranges)
(force whitespace-ranges)
(force blank-ranges)
(force iso-control-ranges))))
((names ...) (map (lambda (sym)
(datum->syntax-object (syntax ctxt) sym #f))
'(alphabetic
lower-case
upper-case
title-case
numeric
symbolic
punctuation
graphic
whitespace
blank
iso-control))))
(syntax (define-lex-abbrevs (names ranges) ...))))))
(define-lex-abbrev any-char (char-complement (union)))
(define-lex-abbrev any-string (intersection))
(define-lex-abbrev nothing (union))
(create-unicode-abbrevs #'here)
(define-lex-trans (char-set stx)
(syntax-case stx ()
((_ str)
(string? (syntax-e (syntax str)))
(with-syntax (((char ...) (string->list (syntax-e (syntax str)))))
(syntax (union char ...))))))
(define-syntax provide-lex-keyword
(syntax-rules ()
[(_ id ...)
(begin
(define-syntax-parameter id
(make-set!-transformer
(lambda (stx)
(raise-syntax-error
#f
(format "use of a lexer keyword (~a) is not in an appropriate lexer action"
'id)
stx))))
...
(provide id ...))]))
(provide-lex-keyword start-pos end-pos lexeme input-port return-without-pos)
) )

Loading…
Cancel
Save