rename ??,?@ to ~?,~@ (see PR #2031)

This commit is contained in:
Ryan Culpepper 2018-04-06 11:42:29 +02:00
parent 5bb2c1f16e
commit 84ca256029
10 changed files with 103 additions and 94 deletions

View File

@ -270,7 +270,7 @@ the individual @racket[stx-expr].
(math 3 1 4 1 5 9)
]}
@defform[#:literals (?? ?@) (syntax template)
@defform[#:literals (~? ~@) (syntax template)
#:grammar
([template id
(head-template ...)
@ -278,16 +278,16 @@ the individual @racket[stx-expr].
(code:line #,(tt "#")(head-template ...))
(code:line #,(tt "#&")template)
(code:line #,(tt "#s")(key-datum head-template ...))
(?? template template)
(~? template template)
(ellipsis stat-template)
const]
[head-template template
(code:line head-template ellipsis ...+)
(?@ . template)
(?? head-template head-template)
(?? head-template)]
(~@ . template)
(~? head-template head-template)
(~? head-template)]
[stat-template @#,elem{like @svar{template}, but without @|lit-ellipsis|,
@racket[??], and @racket[?@]}]
@racket[~?], and @racket[~@]}]
[ellipsis #,lit-ellipsis])]{
Constructs a syntax object based on a @racket[template], which can
@ -297,7 +297,7 @@ include @tech{pattern variables} bound by @racket[syntax-case] or
A @svar[template] produces a single syntax object. A
@svar[head-template] produces a sequence of zero or more syntax
objects. A @svar[stat-template] is like a @svar[template], except that
@|lit-ellipsis|, @racket[??], and @racket[?@] are interpreted as
@|lit-ellipsis|, @racket[~?], and @racket[~@] are interpreted as
constants instead of template forms.
A @svar[template] produces a syntax object as follows:
@ -350,7 +350,7 @@ A @svar[template] produces a syntax object as follows:
The @racket[key-datum] must correspond to a valid first argument of
@racket[make-prefab-struct].}
@specsubform[#:literals (??) (?? template1 template2)]{
@specsubform[#:literals (~?) (~? template1 template2)]{
Produces the result of @racket[template1] if @racket[template1] has no
pattern variables with ``missing values''; otherwise, produces the result of
@ -363,16 +363,16 @@ A @svar[template] produces a syntax object as follows:
@examples[#:eval (let ([ev (syntax-eval)]) (ev '(require syntax/parse/pre)) ev)
(syntax-parse #'(m 1 2 3)
[(_ (~optional (~seq #:op op:expr)) arg:expr ...)
#'((?? op +) arg ...)])
#'((~? op +) arg ...)])
(syntax-parse #'(m #:op max 1 2 3)
[(_ (~optional (~seq #:op op:expr)) arg:expr ...)
#'((?? op +) arg ...)])
#'((~? op +) arg ...)])
]}
@specsubform[(ellipsis stat-template)]{
Produces the same result as @racket[stat-template], which is like a
@racket[template], but @racket[...], @racket[??], and @racket[?@]
@racket[template], but @racket[...], @racket[~?], and @racket[~@]
are treated like an @racket[id] (with no pattern binding).}
@specsubform[const]{
@ -414,7 +414,7 @@ A @racket[head-template] produces a sequence of syntax objects; that sequence is
not occur at a depth less than its @tech{depth marker}; otherwise, an error is
raised.}
@specsubform[#:literals (?@) (?@ . template)]{
@specsubform[#:literals (~@) (~@ . template)]{
Produces the sequence of elements in the syntax list produced by
@racket[template]. If @racket[template] does not produce a proper syntax list,
@ -423,23 +423,23 @@ A @racket[head-template] produces a sequence of syntax objects; that sequence is
@examples[#:eval (syntax-eval)
(with-syntax ([(key ...) #'('a 'b 'c)]
[(val ...) #'(1 2 3)])
#'(hash (?@ key val) ...))
#'(hash (~@ key val) ...))
(with-syntax ([xs #'(2 3 4)])
#'(list 1 (?@ . xs) 5))
#'(list 1 (~@ . xs) 5))
]}
@specsubform[#:literals (??) (?? head-template1 head-template2)]{
@specsubform[#:literals (~?) (~? head-template1 head-template2)]{
Produces the result of @racket[head-template1] if none of its pattern
variables have ``missing values''; otherwise produces the result of
@racket[head-template2]. }
@specsubform[#:literals (??) (?? head-template)]{
@specsubform[#:literals (~?) (~? head-template)]{
Produces the result of @racket[head-template] if none of its pattern
variables have ``missing values''; otherwise produces nothing.
Equivalent to @racket[(?? head-template (?@))]. }
Equivalent to @racket[(~? head-template (~@))]. }
A @racket[(#,(racketkeywordfont "syntax") template)] form is normally
abbreviated as @racket[#'template]; see also
@ -447,7 +447,7 @@ abbreviated as @racket[#'template]; see also
variables, then @racket[#'template] is equivalent to
@racket[(quote-syntax template)].
@history[#:changed "6.90.0.24" @elem{Added @racket[?@] and @racket[??].}]
@history[#:changed "6.90.0.24" @elem{Added @racket[~@] and @racket[~?].}]
}
@ -569,11 +569,11 @@ where it indicates a pattern that matches any syntax object. See
@racket[syntax-case].}
@deftogether[[
@defidform[??]
@defidform[?@]
@defidform[~?]
@defidform[~@]
]]{
The @racket[??] and @racket[?@] transformer bindings prohibit these forms from
The @racket[~?] and @racket[~@] transformer bindings prohibit these forms from
being used as an expression. The bindings are useful only in syntax templates.
See @racket[syntax].

View File

@ -64,9 +64,9 @@ There's a simpler way of writing the @racket[~or*] pattern above:
]
@section{Optional Arguments with @racket[??]}
@section{Optional Arguments with @racket[~?]}
The @racket[??] template form provides a compact alternative to
The @racket[~?] template form provides a compact alternative to
explicitly testing attribute values. Here's one way to do it:
@interaction[#:eval the-eval
@ -74,11 +74,11 @@ explicitly testing attribute values. Here's one way to do it:
(syntax-parse stx
[(mycond (~optional (~seq #:error-on-fallthrough who:expr))
clause ...)
#'(mycond* (?? (?@ #t who) (?@ #f #f)) clause ...)]))
#'(mycond* (~? (~@ #t who) (~@ #f #f)) clause ...)]))
]
If @racket[who] matched, then the @racket[??] subtemplate splices in
the two terms @racket[#t who] into the enclosing template (@racket[?@]
If @racket[who] matched, then the @racket[~?] subtemplate splices in
the two terms @racket[#t who] into the enclosing template (@racket[~@]
is the template splicing form). Otherwise, it splices in @racket[#f #f].
Here's an alternative definition that re-uses Racket's @racket[cond] macro:
@ -88,15 +88,15 @@ Here's an alternative definition that re-uses Racket's @racket[cond] macro:
(syntax-parse stx
[(mycond (~optional (~seq #:error-on-fallthrough who:expr))
clause ...)
#'(cond clause ... (?? [else (error 'who "no clause matched")] (?@)))]))
#'(cond clause ... (~? [else (error 'who "no clause matched")] (~@)))]))
]
In this version, we optionally insert an @racket[else] clause at the
end to signal the error; otherwise we use @racket[cond]'s fall-through
behavior (that is, returning @racket[(void)]).
If the second subtemplate of a @racket[??] template is
@racket[(?@)]---that is, it produces no terms at all---the second
If the second subtemplate of a @racket[~?] template is
@racket[(~@)]---that is, it produces no terms at all---the second
subtemplate can be omitted.

View File

@ -293,6 +293,14 @@ Equivalent to @racket[syntax], @racket[syntax/loc],
Equivalent to @racket[datum].
}
@deftogether[[
@defidform[??]
@defidform[?@]
]]{
Equivalent to @racket[~?] and @racket[~@], respectively.
}
@defform*[[(define-template-metafunction metafunction-id expr)
(define-template-metafunction (metafunction-id . formals) body ...+)]]{

View File

@ -2623,28 +2623,28 @@
(equal? (syntax-line #'cons) (syntax-line #'one))])))
;; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;; Minimal tests for syntax and ?@, ??
;; Minimal tests for syntax and ~@, ~?
;; More tests in pkgs/racket-test/tests/stxparse/test-syntax.rkt
(test '(a 1 b 2 c 3)
'syntax
(with-syntax ([(x ...) #'(a b c)] [(y ...) #'(1 2 3)])
(syntax->datum #'((?@ x y) ...))))
(syntax->datum #'((~@ x y) ...))))
(test '(1 2 3 4)
'syntax
(with-syntax ([xs #'(2 3)])
(syntax->datum #'(1 (?@ . xs) 4))))
(syntax->datum #'(1 (~@ . xs) 4))))
(test '(1 2 3)
'syntax
(with-syntax ([x #'(1 2 3)])
(syntax->datum #'(?? x "missing"))))
(syntax->datum #'(~? x "missing"))))
(test '(4 5 6)
'syntax
(with-syntax ([(x ...) #'(4 5 6)])
(syntax->datum #'((?? x) ...))))
(syntax->datum #'((~? x) ...))))
;; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

View File

@ -6,7 +6,7 @@
racket/syntax
syntax/parse)
;; Additional tests for syntax w/ ??, ?@, etc
;; Additional tests for syntax w/ ~?, ~@, etc
(define-syntax (tc stx)
(syntax-case stx ()
@ -70,16 +70,16 @@
(tc (syntax (aa ... ((yy ok) ...) ...))
'(a b c ((1 ok) (2 ok) (3 ok)) ((4 ok) (5 ok) (6 ok)) ((7 ok) (8 ok) (9 ok))))
(tc (syntax ((?@ 1 2) 3))
(tc (syntax ((~@ 1 2) 3))
'(1 2 3))
(tc (with-syntax ([w '(1 2 3)])
(syntax ((?@ 0 . w) 4)))
(syntax ((~@ 0 . w) 4)))
'(0 1 2 3 4))
(tc (syntax ((?@ aa ok) ...))
(tc (syntax ((~@ aa ok) ...))
'(a ok b ok c ok))
(tc (syntax ((?@ aa nn) ...))
(tc (syntax ((~@ aa nn) ...))
'(a 1 b 2 c 3))
(tc (syntax (aa ... (?@ nn xx) ...))
(tc (syntax (aa ... (~@ nn xx) ...))
'(a b c 1 x 2 y 3 z))
;; escape
@ -92,10 +92,10 @@
(tc (syntax (yy ... ...))
'(1 2 3 4 5 6 7 8 9))
;; ??
(tc (syntax (?? (ok oo go) nah))
;; ~?
(tc (syntax (~? (ok oo go) nah))
'nah)
(tc (syntax ((?? (ready oo)) done))
(tc (syntax ((~? (ready oo)) done))
'(done))
;; liberal depth rules
@ -118,26 +118,26 @@
(tc (syntax ((aa yy) ... ...))
(syntax->datum #'((aa yy) ... ...)))
;; head ??
;; head ~?
(tc (syntax ((?? (?@ #:yes uu) (?@ #:no)) done))
(tc (syntax ((~? (~@ #:yes uu) (~@ #:no)) done))
'(#:yes abc done))
(tc (syntax ((?? (?@ #:yes oo) (?@ #:no)) done))
(tc (syntax ((~? (~@ #:yes oo) (~@ #:no)) done))
'(#:no done))
(tc (syntax ((?? (?@ #:yes pp) (?@ #:no)) ...))
(tc (syntax ((~? (~@ #:yes pp) (~@ #:no)) ...))
'(#:no #:yes 1 #:no #:yes 2 #:yes 3))
;; ----------------------------------------
;; combined ?? ?@
;; combined ~? ~@
(tc (syntax-parse #'(a b c 1 2 3)
[(a:id ... (~optional s:str) n:nat ...)
(syntax (a ... n ... (?@ . (?? (string: s) ()))))])
(syntax (a ... n ... (~@ . (~? (string: s) ()))))])
'(a b c 1 2 3))
(tc (syntax-parse #'(a b c "hello!" 1 2 3)
[(a:id ... (~optional s:str) n:nat ...)
(syntax (a ... n ... (?@ . (?? (string: s) ()))))])
(syntax (a ... n ... (~@ . (~? (string: s) ()))))])
'(a b c 1 2 3 string: "hello!"))
;; ----------------------------------------
@ -173,10 +173,10 @@
(terx (syntax aa)
#rx"missing ellipsis with pattern variable in template")
(terx (syntax (?@))
(terx (syntax (~@))
#rx"illegal use")
(terx (syntax ((?@ . uu)))
(terx (syntax ((~@ . uu)))
#rx"splicing template did not produce a syntax list")
(terx (with-syntax ([(bb ...) #'(y z)]) (syntax ((aa bb) ...)))
@ -202,14 +202,14 @@
(tloc syntax/loc (aa ... . 1) #t)
(with-syntax ([(z ...) '()])
(tloc syntax/loc (z ... . 2) #f)) ;; zero iters + syntax tail => no relocation
(tloc syntax/loc ((?@ aa ...) 2) #t)
(tloc syntax/loc ((?@ aa ...) . 2) #t)
(tloc syntax/loc ((~@ aa ...) 2) #t)
(tloc syntax/loc ((~@ aa ...) . 2) #t)
(with-syntax ([lst #'(a b c)] [nil #'()])
(tloc syntax/loc ((?@ . lst) 2) #t)
(tloc syntax/loc ((?@ . lst) . 2) #t)
(tloc syntax/loc ((?@ . nil) 2) #t)
(tloc syntax/loc ((?@ . nil) . 2) #f)) ;; empty + syntax tail => no relocation
(tloc syntax/loc (?? 1 2) #t)
(tloc syntax/loc ((~@ . lst) 2) #t)
(tloc syntax/loc ((~@ . lst) . 2) #t)
(tloc syntax/loc ((~@ . nil) 2) #t)
(tloc syntax/loc ((~@ . nil) . 2) #f)) ;; empty + syntax tail => no relocation
(tloc syntax/loc (~? 1 2) #t)
(tloc quasisyntax/loc uu #f)
(tloc quasisyntax/loc lambda #t)
@ -271,7 +271,7 @@
(check-equal? counter 5)
(void)])))
(test-case "lazy syntax-valued attributes, ??, ?@"
(test-case "lazy syntax-valued attributes, ~?, ~@"
(let ()
(define-syntax-class foo
(pattern n:nat
@ -294,41 +294,41 @@
'(() () () (2) () (2 3) ())))
(check-exn #rx"attribute contains non-syntax value"
(lambda () (syntax (n.half ...))))
(let ([halves (syntax ((?? n.half) ...))])
(let ([halves (syntax ((~? n.half) ...))])
(check-pred syntax? halves)
(check-equal? (syntax->datum halves)
'(1 2 3)))
(void)])))
;; ----------------------------------------
;; Testing raise/handlers-based ?? (used to be based on drivers check)
;; Testing raise/handlers-based ~? (used to be based on drivers check)
(tc (syntax-parse #'()
[((~optional abs))
(syntax (?? (?? abs inner) outer))])
(syntax (~? (~? abs inner) outer))])
'inner)
;; test from ianj, 11/18/2013
(tc (syntax-parse #'(a)
[(a:expr (~optional b:expr))
(syntax (?? '(a (?? b 0)) 0))])
(syntax (~? '(a (~? b 0)) 0))])
''(a 0))
(define/syntax-parse ((~or* i:id n:nat) ...) '(a b 1 2 3 4))
;; note: i,n both 6 elts long
(tc (syntax ((?? i X) ...))
(tc (syntax ((~? i X) ...))
'(a b X X X X))
(tc (syntax ((?? i n) ...))
(tc (syntax ((~? i n) ...))
'(a b 1 2 3 4))
(tc (syntax ((?? i) ...)) '(a b))
(tc (syntax ((?? n) ...)) '(1 2 3 4))
(tc (syntax (?? (i ...) no)) 'no)
(tc (syntax (?? (n ...) no)) 'no)
(tc (syntax ((~? i) ...)) '(a b))
(tc (syntax ((~? n) ...)) '(1 2 3 4))
(tc (syntax (~? (i ...) no)) 'no)
(tc (syntax (~? (n ...) no)) 'no)
;; test from ianj, 5/14/2014
(tc (syntax-parse #'(A)
[(x:id (~optional (~seq #:a [a b] ...)))
(syntax (?? (hash (?@ a b) ...) x))])
(syntax (~? (hash (~@ a b) ...) x))])
'A)

View File

@ -1,15 +1,15 @@
(module ellipses '#%kernel
(#%require (for-syntax '#%kernel))
(#%provide ... _ ?? ?@)
(#%provide ... _ ~? ~@)
(define-syntaxes (...)
(lambda (stx)
(raise-syntax-error #f "ellipses not allowed as an expression" stx)))
(define-syntaxes (??)
(define-syntaxes (~?)
(lambda (stx) (raise-syntax-error #f "not allowed as an expression" stx)))
(define-syntaxes (?@)
(define-syntaxes (~@)
(lambda (stx) (raise-syntax-error #f "not allowed as an expression" stx)))
(define-syntaxes (_)

View File

@ -105,7 +105,7 @@
[ctx (datum->syntax #'x 'ctx #'x)])
(convert-k (datum->syntax
stx
(cons #'(?@! . temp) rest-v)
(cons #'(~@! . temp) rest-v)
stx
stx)
(with-syntax ([check check-splicing-list-id])

View File

@ -56,4 +56,4 @@
#'id))])))
(#%provide syntax/loc quote-syntax/prune syntax-case* syntax-case datum-case
... _ ?? ?@))
... _ ~? ~@))

View File

@ -10,8 +10,8 @@
(#%provide syntax
syntax/loc
datum
?? ?@
?@! signal-absent-pvar
~? ~@
~@! signal-absent-pvar
(protect
(for-syntax attribute-mapping
attribute-mapping?
@ -30,18 +30,18 @@
;; - (metafunction . T)
;; - (H . T)
;; - (H ... . T), (H ... ... . T), etc
;; - (... T) -- escapes inner ..., ??, ?@
;; - (?? T T)
;; - (... T) -- escapes inner ..., ~?, ~@
;; - (~? T T)
;; - #(T*) -- actually, vector->list interpreted as T
;; - #s(prefab-struct-key T*) -- likewise
;; A HeadTemplate (H) is one of:
;; - T
;; - (?? H)
;; - (?? H H)
;; - (?@ . T)
;; - (~? H)
;; - (~? H H)
;; - (~@ . T)
(define-syntax ?@! #f) ;; private, escape-ignoring version of ?@, used by unsyntax-splicing
(define-syntax ~@! #f) ;; private, escape-ignoring version of ~@, used by unsyntax-splicing
;; ============================================================
;; Compile-time
@ -205,7 +205,7 @@
(define-values (drivers guide) (parse-t (cadr t) depth #t))
;; Preserve t-escaped so that (t-escaped (t-const _)) != (t-const _)
(values drivers `(t-escaped ,guide)))]
[(parse-form t (quote-syntax ??) 2)
[(parse-form t (quote-syntax ~?) 2)
=> (lambda (t)
(disappeared! (car t))
(define t1 (cadr t))
@ -293,8 +293,8 @@
(cond [(identifier? t)
(cond [(and (not esc?)
(or (free-identifier=? t (quote-syntax ...))
(free-identifier=? t (quote-syntax ??))
(free-identifier=? t (quote-syntax ?@))))
(free-identifier=? t (quote-syntax ~?))
(free-identifier=? t (quote-syntax ~@))))
(wrong-syntax t "illegal use")]
[(lookup-metafun t)
(wrong-syntax t "illegal use of syntax metafunction")]
@ -328,12 +328,12 @@
;; parse-h : Syntax Nat Boolean -> (values (dsetof PVar) HeadGuide)
(define (parse-h h depth esc?)
(cond [(and (not esc?) (parse-form h (quote-syntax ??) 1))
(cond [(and (not esc?) (parse-form h (quote-syntax ~?) 1))
=> (lambda (h)
(disappeared! (car h))
(define-values (drivers guide) (parse-h (cadr h) depth esc?))
(values drivers `(h-orelse ,guide null)))]
[(and (not esc?) (parse-form h (quote-syntax ??) 2))
[(and (not esc?) (parse-form h (quote-syntax ~?) 2))
=> (lambda (h)
(disappeared! (car h))
(define-values (drivers1 guide1) (parse-h (cadr h) depth esc?))
@ -345,8 +345,8 @@
[(and (stx-pair? h)
(let ([h-head (stx-car h)])
(and (identifier? h-head)
(or (and (free-identifier=? h-head (quote-syntax ?@)) (not esc?))
(free-identifier=? h-head (quote-syntax ?@!))))))
(or (and (free-identifier=? h-head (quote-syntax ~@)) (not esc?))
(free-identifier=? h-head (quote-syntax ~@!))))))
(disappeared! (stx-car h))
(define-values (drivers guide) (parse-t (stx-cdr h) depth esc?))
(values drivers `(h-splice ,guide (quote ,h) (quote-syntax ,(stx-car h))))]
@ -690,7 +690,7 @@
(define absent-pvar-escape-key (gensym 'absent-pvar-escape))
;; signal-absent-pvar : -> escapes or #f
;; Note: Only escapes if in ?? form.
;; Note: Only escapes if in ~? form.
(define (signal-absent-pvar)
(let ([escape (continuation-mark-set-first #f absent-pvar-escape-key)])
(if escape (escape) #f)))

View File

@ -5,8 +5,9 @@
(provide (rename-out [syntax template]
[syntax/loc template/loc]
[quasisyntax quasitemplate]
[quasisyntax/loc quasitemplate/loc])
?? ?@
[quasisyntax/loc quasitemplate/loc]
[~? ??]
[~@ ?@])
define-template-metafunction)
;; ============================================================