syntax/parse: added litset extension
This commit is contained in:
parent
e5e12ab01a
commit
1bf95392d2
|
@ -64,13 +64,50 @@
|
||||||
(raise-syntax-error #f "expected phase-level (exact integer or #f)" ctx stx))
|
(raise-syntax-error #f "expected phase-level (exact integer or #f)" ctx stx))
|
||||||
stx)
|
stx)
|
||||||
|
|
||||||
|
(define-for-syntax (check-litset-list stx ctx)
|
||||||
|
(syntax-case stx ()
|
||||||
|
[(litset-id ...)
|
||||||
|
(for/list ([litset-id (syntax->list #'(litset-id ...))])
|
||||||
|
(let* ([val (and (identifier? litset-id)
|
||||||
|
(syntax-local-value/record litset-id literalset?))])
|
||||||
|
(if val
|
||||||
|
(cons litset-id val)
|
||||||
|
(raise-syntax-error #f "expected literal set name" ctx litset-id))))]
|
||||||
|
[_ (raise-syntax-error #f "expected list of literal set names" ctx stx)]))
|
||||||
|
|
||||||
|
;; check-literal-entry/litset : stx stx -> (list id id)
|
||||||
|
(define-for-syntax (check-literal-entry/litset stx ctx)
|
||||||
|
(syntax-case stx ()
|
||||||
|
[(internal external)
|
||||||
|
(and (identifier? #'internal) (identifier? #'external))
|
||||||
|
(list #'internal #'external)]
|
||||||
|
[id
|
||||||
|
(identifier? #'id)
|
||||||
|
(list #'id #'id)]
|
||||||
|
[_ (raise-syntax-error #f "expected literal entry" ctx stx)]))
|
||||||
|
|
||||||
|
(define-for-syntax (check-duplicate-literals stx imports lits)
|
||||||
|
(let ([lit-t (make-hasheq)]) ;; sym => #t
|
||||||
|
(define (check+enter! key blame-stx)
|
||||||
|
(when (hash-ref lit-t key #f)
|
||||||
|
(raise-syntax-error #f (format "duplicate literal: ~a" key) stx blame-stx))
|
||||||
|
(hash-set! lit-t key #t))
|
||||||
|
(for ([id+litset (in-list imports)])
|
||||||
|
(let ([litset-id (car id+litset)]
|
||||||
|
[litset (cdr id+litset)])
|
||||||
|
(for ([entry (in-list (literalset-literals litset))])
|
||||||
|
(check+enter! (car entry) litset-id))))
|
||||||
|
(for ([lit (in-list lits)])
|
||||||
|
(check+enter! (syntax-e (car lit)) (car lit)))))
|
||||||
|
|
||||||
(define-syntax (define-literal-set stx)
|
(define-syntax (define-literal-set stx)
|
||||||
(syntax-case stx ()
|
(syntax-case stx ()
|
||||||
[(define-literal-set name . rest)
|
[(define-literal-set name . rest)
|
||||||
(let-values ([(chunks rest)
|
(let-values ([(chunks rest)
|
||||||
(parse-keyword-options
|
(parse-keyword-options
|
||||||
#'rest
|
#'rest
|
||||||
`((#:phase ,check-phase-level)
|
`((#:literal-sets ,check-litset-list)
|
||||||
|
(#:phase ,check-phase-level)
|
||||||
(#:for-template)
|
(#:for-template)
|
||||||
(#:for-syntax)
|
(#:for-syntax)
|
||||||
(#:for-label))
|
(#:for-label))
|
||||||
|
@ -86,9 +123,13 @@
|
||||||
[else (options-select-value chunks '#:phase #:default 0)])]
|
[else (options-select-value chunks '#:phase #:default 0)])]
|
||||||
[lits (syntax-case rest ()
|
[lits (syntax-case rest ()
|
||||||
[( (lit ...) )
|
[( (lit ...) )
|
||||||
(check-literals-list/litset #'(lit ...) stx)]
|
(for/list ([lit (in-list (syntax->list #'(lit ...)))])
|
||||||
[_ (raise-syntax-error #f "bad syntax" stx)])])
|
(check-literal-entry/litset lit stx))]
|
||||||
|
[_ (raise-syntax-error #f "bad syntax" stx)])]
|
||||||
|
[imports (options-select-value chunks '#:literal-sets #:default null)])
|
||||||
|
(check-duplicate-literals stx imports lits)
|
||||||
(with-syntax ([((internal external) ...) lits]
|
(with-syntax ([((internal external) ...) lits]
|
||||||
|
[(litset-id ...) (map car imports)]
|
||||||
[relphase relphase])
|
[relphase relphase])
|
||||||
#`(begin
|
#`(begin
|
||||||
(define phase-of-literals
|
(define phase-of-literals
|
||||||
|
@ -97,13 +138,23 @@
|
||||||
'relphase))
|
'relphase))
|
||||||
(define-syntax name
|
(define-syntax name
|
||||||
(make-literalset
|
(make-literalset
|
||||||
(list (list 'internal (quote-syntax external)) ...)
|
(append (literalset-literals (syntax-local-value (quote-syntax litset-id)))
|
||||||
(quote-syntax phase-of-literals)))
|
...
|
||||||
|
(list (list 'internal
|
||||||
|
(quote-syntax external)
|
||||||
|
(quote-syntax phase-of-literals))
|
||||||
|
...))))
|
||||||
(begin-for-syntax/once
|
(begin-for-syntax/once
|
||||||
(for ([x (in-list (syntax->list #'(external ...)))])
|
(for ([x (in-list (syntax->list #'(external ...)))])
|
||||||
(unless (identifier-binding x 'relphase)
|
(unless (identifier-binding x 'relphase)
|
||||||
(raise-syntax-error #f
|
(raise-syntax-error #f
|
||||||
(format "literal is unbound in phase ~a" 'relphase)
|
(format "literal is unbound in phase ~a~a"
|
||||||
|
'relphase
|
||||||
|
(case 'relphase
|
||||||
|
((1) " (for-syntax)")
|
||||||
|
((-1) " (for-template)")
|
||||||
|
((#f) " (for-label)")
|
||||||
|
(else "")))
|
||||||
(quote-syntax #,stx) x))))))))]))
|
(quote-syntax #,stx) x))))))))]))
|
||||||
|
|
||||||
(define-syntax (phase-of-enclosing-module stx)
|
(define-syntax (phase-of-enclosing-module stx)
|
||||||
|
|
|
@ -81,9 +81,9 @@ A ConventionRule is (list regexp DeclEntry)
|
||||||
|
|
||||||
#|
|
#|
|
||||||
A LiteralSet is
|
A LiteralSet is
|
||||||
(make-literalset (listof (list symbol id)) stx)
|
(make-literalset (listof (list symbol id phase-var-id)))
|
||||||
|#
|
|#
|
||||||
(define-struct literalset (literals phase) #:transparent)
|
(define-struct literalset (literals) #:transparent)
|
||||||
|
|
||||||
;; make-dummy-stxclass : identifier -> SC
|
;; make-dummy-stxclass : identifier -> SC
|
||||||
;; Dummy stxclass for calculating attributes of recursive stxclasses.
|
;; Dummy stxclass for calculating attributes of recursive stxclasses.
|
||||||
|
|
|
@ -57,9 +57,6 @@
|
||||||
[check-stxclass-application
|
[check-stxclass-application
|
||||||
(-> syntax? syntax?
|
(-> syntax? syntax?
|
||||||
(cons/c identifier? arguments?))]
|
(cons/c identifier? arguments?))]
|
||||||
[check-literals-list/litset
|
|
||||||
(-> syntax? syntax?
|
|
||||||
(listof (list/c identifier? identifier?)))]
|
|
||||||
[check-conventions-rules
|
[check-conventions-rules
|
||||||
(-> syntax? syntax?
|
(-> syntax? syntax?
|
||||||
(listof (list/c regexp? any/c)))]
|
(listof (list/c regexp? any/c)))]
|
||||||
|
@ -1320,29 +1317,6 @@ A syntax class is integrable if
|
||||||
(raise-syntax-error #f "expected literal entry"
|
(raise-syntax-error #f "expected literal entry"
|
||||||
ctx stx)]))
|
ctx stx)]))
|
||||||
|
|
||||||
;; Literal sets - Definition
|
|
||||||
|
|
||||||
;; check-literals-list/litset : stx stx -> (listof (list id id))
|
|
||||||
(define (check-literals-list/litset stx ctx)
|
|
||||||
(let ([lits (for/list ([x (in-list (stx->list stx))])
|
|
||||||
(check-literal-entry/litset x ctx))])
|
|
||||||
(let ([dup (check-duplicate-identifier (map car lits))])
|
|
||||||
(when dup (raise-syntax-error #f "duplicate literal identifier" ctx dup)))
|
|
||||||
lits))
|
|
||||||
|
|
||||||
;; check-literal-entry/litset : stx stx -> (list id id)
|
|
||||||
(define (check-literal-entry/litset stx ctx)
|
|
||||||
(syntax-case stx ()
|
|
||||||
[(internal external)
|
|
||||||
(and (identifier? #'internal) (identifier? #'external))
|
|
||||||
(list #'internal #'external)]
|
|
||||||
[id
|
|
||||||
(identifier? #'id)
|
|
||||||
(list #'id #'id)]
|
|
||||||
[_
|
|
||||||
(raise-syntax-error #f "expected literal entry"
|
|
||||||
ctx stx)]))
|
|
||||||
|
|
||||||
;; Literal sets - Import
|
;; Literal sets - Import
|
||||||
|
|
||||||
;; check-literal-sets-list : stx stx -> (listof (listof (list id id ct-phase^2)))
|
;; check-literal-sets-list : stx stx -> (listof (listof (list id id ct-phase^2)))
|
||||||
|
@ -1365,7 +1339,7 @@ A syntax class is integrable if
|
||||||
(list (datum->syntax lctx (car entry) stx)
|
(list (datum->syntax lctx (car entry) stx)
|
||||||
(cadr entry)
|
(cadr entry)
|
||||||
phase
|
phase
|
||||||
(literalset-phase litset))))
|
(caddr entry))))
|
||||||
(syntax-case stx ()
|
(syntax-case stx ()
|
||||||
[(litset . more)
|
[(litset . more)
|
||||||
(and (identifier? #'litset))
|
(and (identifier? #'litset))
|
||||||
|
|
|
@ -15,20 +15,24 @@ As a remedy, @schememodname[syntax/parse] offers @deftech{literal
|
||||||
sets}. A literal set is defined via @scheme[define-literal-set] and
|
sets}. A literal set is defined via @scheme[define-literal-set] and
|
||||||
used via the @scheme[#:literal-set] option of @scheme[syntax-parse].
|
used via the @scheme[#:literal-set] option of @scheme[syntax-parse].
|
||||||
|
|
||||||
@defform/subs[(define-literal-set name-id maybe-phase (literal ...))
|
@defform/subs[(define-literal-set id maybe-phase maybe-imports (literal ...))
|
||||||
([literal literal-id
|
([literal literal-id
|
||||||
(pattern-id literal-id)]
|
(pattern-id literal-id)]
|
||||||
[maybe-phase (code:line)
|
[maybe-phase (code:line)
|
||||||
(code:line #:for-template)
|
(code:line #:for-template)
|
||||||
(code:line #:for-syntax)
|
(code:line #:for-syntax)
|
||||||
(code:line #:for-label)
|
(code:line #:for-label)
|
||||||
(code:line #:phase phase-level)])]{
|
(code:line #:phase phase-level)]
|
||||||
|
[maybe-imports (code:line)
|
||||||
|
(code:line #:literal-sets (imported-litset-id ...))])]{
|
||||||
|
|
||||||
Defines @scheme[name] as a @tech{literal set}. Each @scheme[literal]
|
Defines @scheme[id] as a @tech{literal set}. Each @scheme[literal] can
|
||||||
can have a separate @scheme[pattern-id] and @scheme[literal-id]. The
|
have a separate @scheme[pattern-id] and @scheme[literal-id]. The
|
||||||
@scheme[pattern-id] determines what identifiers in the pattern are
|
@scheme[pattern-id] determines what identifiers in the pattern are
|
||||||
treated as literals. The @scheme[literal-id] determines what
|
treated as literals. The @scheme[literal-id] determines what
|
||||||
identifiers the literal matches.
|
identifiers the literal matches. If the @racket[#:literal-sets] option
|
||||||
|
is present, the contents of the given @racket[imported-litset-id]s are
|
||||||
|
included.
|
||||||
|
|
||||||
@myexamples[
|
@myexamples[
|
||||||
(define-literal-set def-litset
|
(define-literal-set def-litset
|
||||||
|
|
|
@ -1,30 +1,10 @@
|
||||||
#lang scheme
|
#lang racket/base
|
||||||
(require syntax/parse
|
(require syntax/parse
|
||||||
syntax/parse/debug
|
syntax/parse/debug
|
||||||
rackunit
|
rackunit
|
||||||
"setup.rkt")
|
"setup.rkt")
|
||||||
(require (for-syntax syntax/parse))
|
(require (for-syntax syntax/parse))
|
||||||
|
|
||||||
#|
|
|
||||||
(module a racket
|
|
||||||
(require syntax/parse)
|
|
||||||
(define-literal-set lits (begin))
|
|
||||||
(provide lits))
|
|
||||||
(module b racket
|
|
||||||
(require (for-syntax 'a syntax/parse))
|
|
||||||
(require (for-syntax syntax/parse/private/runtime))
|
|
||||||
(define-syntax (snarf stx)
|
|
||||||
;;(printf "slpl of snarf: ~s\n" (syntax-local-phase-level))
|
|
||||||
(syntax-parse stx
|
|
||||||
#:literal-sets (lits)
|
|
||||||
[(snarf (begin e)) #'e]))
|
|
||||||
(provide snarf))
|
|
||||||
(module c racket
|
|
||||||
(require (for-syntax 'b racket/base))
|
|
||||||
(begin-for-syntax
|
|
||||||
(displayln (snarf (begin 5)))))
|
|
||||||
|#
|
|
||||||
|
|
||||||
(define-literal-set lits0 #:phase 0
|
(define-literal-set lits0 #:phase 0
|
||||||
(define lambda))
|
(define lambda))
|
||||||
|
|
||||||
|
@ -87,3 +67,33 @@
|
||||||
'(b))
|
'(b))
|
||||||
;; check that passed lambda is not a literal, but a pattern variable:
|
;; check that passed lambda is not a literal, but a pattern variable:
|
||||||
(check-equal? (syntax->datum (getvar lambda #'(lambda b c))))))
|
(check-equal? (syntax->datum (getvar lambda #'(lambda b c))))))
|
||||||
|
|
||||||
|
;; Litset extension
|
||||||
|
|
||||||
|
(tcerr "litset ext, dup 1"
|
||||||
|
(let ()
|
||||||
|
(define-literal-set lits1 (define))
|
||||||
|
(define-literal-set lits2 #:literal-sets (lits1) (define))
|
||||||
|
(void)))
|
||||||
|
|
||||||
|
(tcerr "litset ext, dup 2"
|
||||||
|
(let ()
|
||||||
|
(define-literal-set lits1 (define))
|
||||||
|
(define-literal-set lits2 (define))
|
||||||
|
(define-literal-set lits3 #:literal-sets (lits1 lits2) ())
|
||||||
|
(void)))
|
||||||
|
|
||||||
|
(test-case "litset ext, works"
|
||||||
|
(let ()
|
||||||
|
(define-literal-set lits1 (define))
|
||||||
|
(define-literal-set lits2 #:literal-sets (lits1) (lambda))
|
||||||
|
(define (go x exp)
|
||||||
|
(check-equal? (syntax-parse x #:literal-sets (lits2)
|
||||||
|
[lambda 'lambda]
|
||||||
|
[define 'define]
|
||||||
|
[_ #f])
|
||||||
|
exp))
|
||||||
|
(go #'lambda 'lambda)
|
||||||
|
(go #'define 'define)
|
||||||
|
(go #'begin #f)
|
||||||
|
(void)))
|
Loading…
Reference in New Issue
Block a user