From 6e6c91c4cdeb034ba59fc04623bf1a102e36a76d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Georges=20Dup=C3=A9ron?= <georges.duperon@gmail.com> Date: Sat, 6 May 2017 03:38:02 +0200 Subject: [PATCH] Closes #5 (?@@ + ?? within used to fail), closes #4 (add examples to the doc) --- private/unsyntax-preparse.rkt | 24 +-- scribblings/examples.scrbl | 292 ++++++++++++++++++++++++++++++++++ scribblings/orig.rkt | 19 +++ scribblings/subtemplate.scrbl | 72 ++++----- test/bug-5.rkt | 20 +++ 5 files changed, 379 insertions(+), 48 deletions(-) create mode 100644 scribblings/examples.scrbl create mode 100644 scribblings/orig.rkt create mode 100644 test/bug-5.rkt diff --git a/private/unsyntax-preparse.rkt b/private/unsyntax-preparse.rkt index 353b65e..97cddb0 100644 --- a/private/unsyntax-preparse.rkt +++ b/private/unsyntax-preparse.rkt @@ -24,6 +24,12 @@ (define-for-syntax lifted (make-parameter #f)) +(begin-for-syntax + (define-syntax-class qq + (pattern {~or {~literal stxparse:??} {~literal ??}})) + (define-syntax-class qa + (pattern {~or {~literal stxparse:?@} {~literal ?@}}))) + (define-for-syntax (pre-parse-unsyntax tmpl depth escapes quasi? form) ;; TODO: a nested quasisubtemplate should escape an unsyntax! (define (ds e) @@ -37,7 +43,7 @@ (define (lift! e) (set-box! (lifted) (cons e (unbox (lifted))))) (syntax-parse tmpl #:literals (unsyntax unsyntax-splicing unquote unquote-splicing - quasitemplate ?? ?if ?cond ?attr ?@ ?@@) + quasitemplate ?if ?cond ?attr ?@@) [({~and u unsyntax} (unquote e)) #:when (and (= escapes 0) quasi?) ;; full unsyntax with #,,e @@ -105,18 +111,18 @@ (recur (ds `(,#'?if ,#'condition ,(ds `(,#'?@ . ,#'v)) ,(ds `(,#'self . ,#'rest)))))] - [({~and self ?cond} [{~literal else}] . rest) - ;; ?cond meta-operator, when the first case has the shape [else] + [({~and self ?cond} [{~literal else}]) + ;; ?cond meta-operator, when the only case has the shape [else] #'(stxparse:?@)] [({~and self ?cond} [{~literal else} . v] . rest) ;; ?cond meta-operator, when the first case has the shape [else . v] - (recur #'(?@ . v))] + (recur (ds `(,#'?@ . ,#'v)))] [({~and self ?@@} . e) ;; Special handling for the special (?@@ . e) meta-operator (with-syntax ([tmp (generate-temporary #'self)] [ooo* (map (λ (_) (quote-syntax …)) (range depth))]) (lift! #`(begin (define/with-syntax tmp - (append* (stx-map*syntax->list #,(form #'e)))) + (append* (stx-map*syntax->list #,(form (recur #'e))))) . ooo*)) #'(stxparse:?@ . tmp))] [({~and self ?attr} condition) @@ -127,17 +133,17 @@ [(:ooo t) ;; Ellipsis used to escape part of a template, i.e. (... escaped) tmpl] ;; tmpl is fully escaped: do not change anything, pass the ... along - [({~and self ??} a b c . rest) + [(self:qq a b c . rest) ;; Extended ?? from syntax/parse with three or more cases (ds `(,#'stxparse:?? ,(recur #'a) ,(recur (ds `(,#'self ,#'b ,#'c . ,#'rest)))))] - [(?? a b) + [(:qq a b) ;; ?? from syntax/parse with two cases (ds `(,#'stxparse:?? ,(recur #'a) ,(recur #'b)))] - [(?? a) + [(:qq a) ;; ?? from syntax/parse with a single case (implicit (?@) as the else case) (ds `(,#'stxparse:?? ,(recur #'a)))] - [(?@ . args) + [(:qa . args) ;; ?@ from syntax/parse (ds `(,#'stxparse:?@ . ,(recur #'args)))] [({~var mf (static template-metafunction? "template metafunction")} . args) diff --git a/scribblings/examples.scrbl b/scribblings/examples.scrbl new file mode 100644 index 0000000..d0203e1 --- /dev/null +++ b/scribblings/examples.scrbl @@ -0,0 +1,292 @@ +#lang scribble/manual + +@(require racket/require + scribble/example + "orig.rkt" + (for-label subtemplate + (only-in syntax/parse/experimental/template) + (subtract-in racket/base subtemplate))) + +@title{Examples} + +This section contains a few (somewhat artificial) examples on how to use +@racketmodname[subtemplate]. Most of the examples here would be more wisely +written as functions, and @racketmodname[syntax/parse] would otherwise be +sufficient with slightly more verbose code. The tools offered by +@racketmodname[subtemplate] are more useful for complex macros, where +boilerplate should be elided as much as possible to leave the true structure +of the macro visible. + +@section{Automatically deriving identifiers using subscripts} + +When an identifier @racket[yᵢ] is encountered in a template, it is +automatically derived from the corresponding @racket[xᵢ]. In the following +example, @racket[tempᵢ] is implicitly bound to +@racket[#'(a/temp b/temp c/temp)], without the need to call +@racket[generate-temporaries]. + +@examples[ + (require subtemplate/override) + (syntax-parse #'(a b c) + [(vᵢ …) + #'([tempᵢ vᵢ] …)])] + +It is common in macros to save an expression in a temporary variable to avoid +executing it twice. The following example builds on the previous one to do so, +without the need to call @racket[generate-temporaries]. Note that the +temporary identifiers generated this way are hygienic: there will be no name +clashes with identifiers from the user, nor with identifiers directly created +by your macro. + +@examples[ + (require racket/require + (for-syntax (subtract-in racket/base subtemplate/override) + subtemplate/override)) + (define-syntax sum + (syntax-parser + [(_ vᵢ …) + #'(let ([tempᵢ vᵢ] …) + (unless (integer? tempᵢ) + (printf "Warning: ~a should be an integer, got ~a.\n" 'vᵢ tempᵢ)) + … + (+ tempᵢ …))])) + (sum 1 2 3) + (sum 1 (begin (displayln "executed once") 2) 3) + (sum 1 (+ 3 0.14) 3)] + +If you run out of unicode subscripts, characters following the last @racket[_] +are treated as the subscript: + +@examples[ + (require subtemplate/override) + (syntax-parse #'(a b c) + [(v_foo …) + #'([temp_foo v_foo] …)])] + +@section{Automatically extracting plain values from syntax objects} + +In most cases, you do not have to call @racket[syntax->datum] anymore, as +@racketmodname[subtemplate] implicitly extracts the value of syntax pattern +variables. Do not rely too much on this feature, though, as future versions +may require explicit escapement with a concise shorthand, like +@racket[,pattern-variable] or @RACKET[#,pattern-variable]. + +@examples[ + #:escape UNSYNTAX + (require racket/require + (for-syntax (subtract-in racket/base subtemplate/override) + subtemplate/override)) + (define-syntax nested + (syntax-parser + [(_ n v) + (if (> n 0) (code:comment "No need for syntax-e") + #`(list (nested #,(sub1 n) v)) (code:comment "No need for syntax-e") + #'v)])) + (nested 5 '(a b c))] + +The implicit @racket[syntax->datum] also works on pattern variables which have +a non-zero ellipsis depth: + +@examples[ + (require subtemplate/override) + (syntax-parse #'(1 2 3 4 5) + [(v …) + (define sum (apply + v)) + (if (> sum 10) + "foo" + "bar")])] + +@section{Function application enhancements} + +Why bother ourselves with @racket[apply]? Let's just write what we want: + +@examples[ + (require subtemplate/override) + (syntax-parse #'(1 2 3 4 5) + [(v …) + (if (> (+ v …) 10) + "foo" + "bar")])] + +Ellipses work as you expect when used in expressions: + +@examples[ + (require subtemplate/override) + (define/syntax-parse ((vᵢⱼ …) …) #'((1 2 3 4) (5 6))) + (define/with-syntax (xₖ …) #'(a b c)) + (+ vᵢⱼ … …) + (define average (/ (+ vᵢⱼ … …) (length (list vᵢⱼ … …)))) + average + (max (min vᵢⱼ …) …) + (list vᵢⱼ … … xₖ …) + (list (list (+ vᵢⱼ 1) …) … (symbol->string xₖ) …) + (list (list vᵢⱼ …) … xₖ …) + (code:comment "Automatically derived symbols:") + (list (list yᵢⱼ …) …) + (list yₖ …) + (code:comment "Same ids as the yₖ ones above:") + #'(yₖ …) + ] + +Here is another trick with ellipses: @racket[((vᵢ …) …)] should normally call +@racket[1] with arguments @racket[2 3 4], and @racket[5] with the argument +@racket[6], and then call the result of the first with the result of the +second as an argument. Since in most cases this is not what you want, the +@racket[list] function is implicitly called when the second element of an +application form is an ellipsis (do not abuse it, the semantics are a bit at +odds with the usual ones in Racket and might be surprising for people reading +your code): + +@examples[ + (require subtemplate/override) + (define/syntax-parse ((vᵢⱼ …) …) #'((1 2 3 4) (5 6))) + ((vᵢⱼ …) …) + (vᵢⱼ … …) + (((+ vᵢⱼ 1000) …) …) + (code:comment "Automatically derived symbols:") + ((yᵢⱼ …) …) + (yᵢⱼ … …)] + +Ellipses surprisingly also work on @racket[define], +@racket[define/with-syntax] and @racket[define/syntax-parse]: + +@examples[ + (require subtemplate/override) + (define/syntax-parse ((v …) …) #'((1 2 3 4) (5 6))) + (define/syntax-parse (x …) #'("a" "b" "c")) + (begin + (define w (+ v 1)) … … + (define/syntax-parse y:id (string->symbol x)) …) + w + #'(y …)] + +Since the trick is pulled off by a custom @racket[begin] form, provided by +@racketmodname[subtemplate], it will not work as expected at the REPL unless +you explicitly wrap the define and ellipses with a @racket[begin] form, as +done above. Within a module, however, this should work fine. + +@section{Ellipsis-preserving @racket[unsyntax]} + +Racket's @orig:syntax and @orig:template from +@racketmodname[syntax/parse/experimental/template] both forget the current +ellipsis position within an @racket[unsyntax] form. This makes it difficult to +perform simple changes to each element of a pattern variable under ellipses. +@racketmodname[syntax/parse/experimental/template] provides template +metafunctions, but they are unpractical for one-off small-scale alterations. +With @racket[subtemplate], @RACKET[#,e] and @RACKET[#,@e] both preserve the +current ellipsis position, meaning that uses of @racket[syntax], +@racket[quasisyntax], @racket[template] and so on within @racket[e] will use +the currently-focused portion of pattern variables under ellipses. + +@examples[ + #:escape UNSYNTAX + (require subtemplate/override racket/list) + (define sd syntax->datum) + (define/syntax-parse ((v …) …) #'((1 2 3 4) (5 6))) + (sd #`(foo #,(+ v …) …)) + (code:comment "Quote, escape, re-quote, re-escape, re-quote:") + (sd #`(foo #,(cons (length (syntax->list #'(v …))) + #`(#,(add1 (syntax-e #'v)) …)) + …)) + (code:comment "Concise version of the above:") + (sd #`(foo (#,(length (v …)) #,(add1 v) …) …)) + (sd #`(foo #,(length (syntax->list #'(v …))) …)) + (sd #`(foo #,(length (list v …)) …)) + (sd #`(foo (#,(add1 v) …) …)) + (sd #`(foo #,(add1 v) … …)) + (sd #`(foo #,@(range v) … …))] + +It is still possible to get the traditional full-escape behaviour with +@RACKET[#,,e] instead of @racket[unsyntax], and @RACKET[#,@,e] or +@RACKET[#,,@e] instead of @racket[unsyntax-splicing]: + +@examples[ + #:escape UNSYNTAX + (require subtemplate/override racket/list syntax/stx) + (define sd syntax->datum) + (define/syntax-parse ((x v …) …) #'((10 1 2 3 4) (100 5 6))) + x + v + (sd #`(foo (x #,,#'(x …)) …)) + (sd #`(foo (x #,,(stx-map (λ (x) (add1 (syntax-e x))) #'(x …))) …)) + (sd #`(foo (x #,,(list (list (add1 v) …) …)) …)) + (sd #`(foo (x #,,(((add1 v) …) …)) …)) + (sd #`(foo (x #,,(stx-map (λ (x) (length (syntax->list x))) + #'((v …) …))) …)) + (sd #`(foo (x #,,((length (v …)) …)) …)) + (sd #`(foo ((v …) #,,((length (v …)) …)) …)) + (sd #`(foo (x #,,@((length (v …)) …)) …)) + (sd #`(foo (x #,@,(range (length (x …)))) …)) + (sd #`(foo (v … #,,@((range (length (v …))) …)) …))] + +@section{Splicing and conditional template elements} + +The splicing form @racket[?@] as well as @racket[??] should be familiar to +users of @racketmodname[syntax/parse/experimental/template]. The +@racketmodname[subtemplate] library provides overridden versions which also +work outside of syntax templates, as well as a few extras: + +@examples[ + (require subtemplate/override) + (define/syntax-parse ({~optional {~or k:keyword b:boolean i:nat}} + {~and {~or (v …) s:str}} …) + #'(#:a-keyword (1 2 3 4) "foo" (5 6))) + (list (?? (+ v …) + (string-length s)) …) + (list (?? (?@ v …) + (string-length s)) …) + (list 'x (?@@ '(y y y) (?? (?@ (list 'c v …))) …) 'z) + (list (?if s "string" "list of numbers") …) + (?cond [k (list (?? (?@ 'there-was-a-keyword v …)) …)] + [b (list (?? (?@ 'there-was-a-boolean (?? v s) …)) …)] + [else (list (?? (?@ (?? i) v …)) …)]) + (list (?attr k) (?attr b) (?attr i)) + (?? k b i 'none)] + +The @racket[?@@] splicing form performs two levels of unwrapping (it can be +understood as a way to perform @racket[(?@ (append elements …))]). The +@racket[(?if _condition _true _false)] is a generalisation of @racket[??], +which accepts a @racket[_condition] template, and produces the +@racket[_true]-template if there are no missing elements in the +@racket[_condition] (in the sense of @racket[~optional]), and produces +@racket[_false] otherwise. @racket[?cond] is a shorthand for a sequence of +nested @racket[?if] forms, and @racket[(?attr a)] returns a boolean indicating +the presence of the attribute (it is a shorthand for @racket[(?if a #t #f)]). +Finally, @racket[??] itself is not limited to two alternatives. When given a +single alternative, @racket[??] implicitly uses @racket[(?@)], i.e. the empty +splice, as the second alternative (this is the behaviour of the version from +@racketmodname[syntax/parse/experimental/template]). When two or more +alternatives are specified, each one is tried in turn, and the last one is +used as a fallback (i.e. an empty splice is @emph{not} implicitly added as a +last alternative when there are already two or more alternatives). + +The @racket[?if] form is useful when one would want to write a @racket[??] +form, where the triggering condition should not appear in the left-hand-side +of @racket[??], for example when changing the generated code based on the +presence of a keyword passed to the macro: + +@examples[ + (require racket/require + (for-syntax (subtract-in racket/base subtemplate/override) + subtemplate/override)) + (define-syntax my-sort + (syntax-parser + [(_ {~optional {~and reverse-kw #:reverse}} v …) + #'(sort (list v …) (?if reverse-kw > <))])) + (my-sort 3 2 1) + (my-sort #:reverse 3 2 1)] + +Note that @racket[?@] and @racket[?@@] work on regular lists (but ellipses do +not), and they can splice multiple arguments into the surrounding function +call. One last application trick is the dotted tail argument, used as a +shorthand for @racket[apply]: + +@examples[ + (require subtemplate/override racket/function) + (define l '((1 2 3) (4 5 6))) + (vector 'a (?@ l) 'c) + (+ 0 (?@@ (?@@ l)) 7) + (vector 'a (?@@ (?@@ l)) 'c) + (+ 0 (?@@ . l) 7) + (vector 'a (?@@ . l) 'c) + (map + . l)] \ No newline at end of file diff --git a/scribblings/orig.rkt b/scribblings/orig.rkt new file mode 100644 index 0000000..747fe9e --- /dev/null +++ b/scribblings/orig.rkt @@ -0,0 +1,19 @@ +#lang racket/base +(require scribble/manual + (for-template syntax/parse + syntax/parse/experimental/template + racket/syntax) + (for-syntax racket/base + racket/syntax)) +(define-syntax (mk stx) + (syntax-case stx () + [(_ id) + (with-syntax ([orig: (format-id #'id "orig:~a" #'id)]) + #'(begin + (define orig: (racket id)) + (provide orig:)))])) +(define-syntax-rule (mk* id ...) (begin (mk id) ...)) + +(mk* syntax-parse syntax-case with-syntax template quasitemplate syntax + unsyntax quasisyntax ?? ?@ template/loc quasitemplate/loc #%app + #%top begin let) \ No newline at end of file diff --git a/scribblings/subtemplate.scrbl b/scribblings/subtemplate.scrbl index 83ca417..194b3e3 100644 --- a/scribblings/subtemplate.scrbl +++ b/scribblings/subtemplate.scrbl @@ -2,32 +2,11 @@ @require[racket/require scriblib/footnote scribble-math + "orig.rkt" @for-label[subtemplate (only-in syntax/parse/experimental/template) (subtract-in racket/base subtemplate)]] -@(begin - (module m racket/base - (require scribble/manual - (for-template syntax/parse - syntax/parse/experimental/template - racket/syntax) - (for-syntax racket/base - racket/syntax)) - (define-syntax (mk stx) - (syntax-case stx () - [(_ id) - (with-syntax ([orig: (format-id #'id "orig:~a" #'id)]) - #'(begin - (define orig: @racket[id]) - (provide orig:)))])) - (define-syntax-rule (mk* id ...) (begin (mk id) ...)) - - (mk* syntax-parse syntax-case with-syntax template quasitemplate syntax - unsyntax quasisyntax ?? ?@ template/loc quasitemplate/loc #%app - #%top begin let)) - (require 'm)) - @title[#:style (with-html5 manual-doc-style)]{Subtemplate} @author[@author+email["Georges Dupéron" "georges.duperon@gmail.com"]] @@ -48,6 +27,8 @@ these are likely to cause problems in your code. Finally, If the maintenance burden is too high, I might drop the compatibility with @racketmodname[syntax/parse] and @|orig:syntax-case|. +@include-section{examples.scrbl} + @section{The main @racketmodname[subtemplate] module} @defmodule[subtemplate]{ @@ -166,25 +147,36 @@ to their equivalents from this library, and without @orig:template/loc] and @subsection{New and overridden bindings provided by @racketmodname[subtemplate]} -@defform*[{(subtemplate template) - (subtemplate template #:properties (prop ...))} +@defform*[{(subtemplate tmpl) + (subtemplate tmpl #:properties (prop ...))} #:contracts ([prop identifier?])]{ - Like @racket[template], but automatically derives identifiers for any - @racket[yᵢ …] which is not bound as a syntax pattern variable, based on a - corresponding @racket[xᵢ …] which is bound as a syntax pattern variable.} + + Like @orig:template from @racketmodname[syntax/parse/experimental/template], + but automatically derives identifiers for any @racket[yᵢ …] which is not bound + as a syntax pattern variable, based on a corresponding @racket[xᵢ …] which is + bound as a syntax pattern variable. Additionally, @racket[subtemplate] + supports a number of features described in + @secref["The_main_subtemplate_module" + #:doc '(lib "subtemplate/scribblings/subtemplate.scrbl")], + which are not part of @racketmodname[syntax/parse/experimental/template]} -@defform*[{(quasisubtemplate template) - (quasisubtemplate template #:properties (prop ...))} +@defform*[{(quasisubtemplate tmpl) + (quasisubtemplate tmpl #:properties (prop ...))} #:contracts ([prop identifier?])]{ - Like @racket[quasitemplate], but automatically derives identifiers for any - @racket[yᵢ …] which is not bound as a syntax pattern variable, based on a - corresponding @racket[xᵢ …] which is bound as a syntax pattern variable, in - the same way as @racket[subtemplate].} + Like @orig:quasitemplate from + @racketmodname[syntax/parse/experimental/template], but automatically derives + identifiers for any @racket[yᵢ …] which is not bound as a syntax pattern + variable, based on a corresponding @racket[xᵢ …] which is bound as a syntax + pattern variable, in the same way as @racket[subtemplate]. Additionally, + @racket[quasisubtemplate] supports a number of features described in + @secref["The_main_subtemplate_module" + #:doc '(lib "subtemplate/scribblings/subtemplate.scrbl")], + which are not part of @racketmodname[syntax/parse/experimental/template]} -@defform*[{(template _template) - (template _template #:properties (prop ...))} +@defform*[{(template tmpl) + (template tmpl #:properties (prop ...))} #:contracts ([prop identifier?])]{ @@ -193,8 +185,8 @@ to their equivalents from this library, and without @orig:template/loc] and (ellipsis-preserving escapes with @racket[unsyntax], support for @racket[?@@], @racket[?attr], @racket[?cond] and @racket[?if]).} -@defform*[{(quasitemplate template) - (quasitemplate template #:properties (prop ...))} +@defform*[{(quasitemplate tmpl) + (quasitemplate tmpl #:properties (prop ...))} #:contracts ([prop identifier?])]{ @@ -221,10 +213,12 @@ to their equivalents from this library, and without @orig:template/loc] and Also works in @racket[template], @racket[subtemplate] and their derivatives.} @defform*[[(?? alt) - (?? alt else)]]{ + (?? alt ...+ else)]]{ Executes @racket[alt], if none of the template variables within is omitted (i.e. bound to @racket[#false] for the current ellipsis iteration). Otherwise, - executes @racket[else]. If @racket[else] is omitted, it defaults to + the next @racket[alt] is considered. If every @racket[alt] contains omitted + template variables, then @racket[else] is excuted. If only one @racket[alt] is + specified, without an @racket[else], then @racket[else] defaults to @racket[(?@)], i.e. the empty splice. Also works in @racket[template], @racket[subtemplate] and their derivatives.} diff --git a/test/bug-5.rkt b/test/bug-5.rkt new file mode 100644 index 0000000..09ba63c --- /dev/null +++ b/test/bug-5.rkt @@ -0,0 +1,20 @@ +#lang racket/base +(require subtemplate/override + rackunit) +(check-equal? (let () + (define/syntax-parse ({~optional + {~or k:keyword b:boolean i:nat}} + {~and {~or (v …) s:str}} …) + #'(#:a-keyword (1 2 3 4) "foo" (5 6))) + #'(l (?@@ (?? (v …)) …))) + '(l 1 2 3 4 5 6)) + + +(check-equal? (let () + (define/syntax-parse ({~optional + {~or k:keyword b:boolean i:nat}} + {~and {~or (v …) s:str}} …) + #'(#:a-keyword (1 2 3 4) "foo" (5 6))) + #'(l (?@@ (?? (v …)) …))) + '(l 1 2 3 4 5 6)) +