Subtemplate
1 Examples
1.1 Automatically deriving identifiers using subscripts
1.2 Automatically extracting plain values from syntax objects
1.3 Function application enhancements
1.4 Ellipsis-preserving unsyntax
1.5 Splicing and conditional template elements
2 The main subtemplate module
2.1 Modules re-provided by subtemplate
2.2 New and overridden bindings provided by subtemplate
subtemplate
quasisubtemplate
template
quasitemplate
?@
?@@
??
?if
?attr
?cond
begin
let
#%intdef-begin
#%app
#%top
…+
3 Overriding the default #' and #`
4 Limitations
4.1 Omitted elements in attributes (via ~optional)
5 Lightweight Subtemplate
subtemplate
subtemplate
quasisubtemplate
8.6

Subtemplate

Georges Dupéron <georges.duperon@gmail.com>

This library should be considered experimental. Although most of the syntax should work in the same way in future versions, the behaviour of some corner cases may change, as I try to find the best semantics.

Also, this library requires some patched versions of syntax-parse and syntax-case, as these do not offer the hooks needed to implement subtemplate. Unfortunately, as the official implementations of syntax-parse and syntax-case evolve, compatibility issues may arise.

If you desire to use this library, please drop me an e-mail (my address is below the title), so that I can keep you informed of upcoming changes, see if these are likely to cause problems in your code.

Finally, If the maintenance burden is too high, I might drop the compatibility with syntax/parse and syntax-case.

1 Examples

This section contains a few (somewhat artificial) examples on how to use subtemplate. Most of the examples here would be more wisely written as functions, and syntax/parse would otherwise be sufficient with slightly more verbose code. The tools offered by 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.

1.1 Automatically deriving identifiers using subscripts

When an identifier yᵢ is encountered in a template, it is automatically derived from the corresponding xᵢ. In the following example, tempᵢ is implicitly bound to #'(a/temp b/temp c/temp), without the need to call generate-temporaries.

Examples:
> (require subtemplate/override)
> (syntax-parse #'(a b c)
    [(vᵢ )
     #'([tempᵢ vᵢ] )])

#<syntax:eval:2:0 ((a/temp a) (b/temp b) (c/temp c))>

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 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)

6

> (sum 1 (begin (displayln "executed once") 2) 3)

executed once

6

> (sum 1 (+ 3 0.14) 3)

Warning: (+ 3 0.14) should be an integer, got 3.14.

7.140000000000001

If you run out of unicode subscripts, characters following the last _ are treated as the subscript:

Examples:
> (require subtemplate/override)
> (syntax-parse #'(a b c)
    [(v_foo )
     #'([temp_foo v_foo] )])

#<syntax:eval:2:0 ((a/temp a) (b/temp b) (c/temp c))>

1.2 Automatically extracting plain values from syntax objects

In most cases, you do not have to call syntax->datum anymore, as 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 ,pattern-variable or #,pattern-variable.

Examples:
> (require racket/require
           (for-syntax (subtract-in racket/base subtemplate/override)
                       subtemplate/override))
> (define-syntax nested
    (syntax-parser
      [(_ n v)
       (if (> n 0) ; No need for syntax-e
           #`(list (nested #,(sub1 n) v)) ; No need for syntax-e
           #'v)]))
> (nested 5 '(a b c))

'((((((a b c))))))

The implicit 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")])

"foo"

1.3 Function application enhancements

Why bother ourselves with 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")])

"foo"

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ᵢⱼ  )

21

> (define average (/ (+ vᵢⱼ  ) (length (list vᵢⱼ  ))))
> average

7/2

> (max (min vᵢⱼ ) )

5

> (list vᵢⱼ   xₖ )

'(1 2 3 4 5 6 a b c)

> (list (list (+ vᵢⱼ 1) )  (symbol->string xₖ) )

'((2 3 4 5) (6 7) "a" "b" "c")

> (list (list vᵢⱼ )  xₖ )

'((1 2 3 4) (5 6) a b c)

; Automatically derived symbols:
> (list (list yᵢⱼ ) )

'((1/y 2/y 3/y 4/y) (5/y 6/y))

> (list yₖ )

'(a/y b/y c/y)

; Same ids as the yₖ ones above:
> #'(yₖ )

#<syntax:eval:13:0 (a/y b/y c/y)>

Here is another trick with ellipses: ((vᵢ ) ) should normally call 1 with arguments 2 3 4, and 5 with the argument 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 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ᵢⱼ ) )

'((1 2 3 4) (5 6))

> (vᵢⱼ  )

'(1 2 3 4 5 6)

> (((+ vᵢⱼ 1000) ) )

'((1001 1002 1003 1004) (1005 1006))

; Automatically derived symbols:
> ((yᵢⱼ ) )

'((1/y 2/y 3/y 4/y) (5/y 6/y))

> (yᵢⱼ  )

'(1/y 2/y 3/y 4/y 5/y 6/y)

Ellipses surprisingly also work on define, define/with-syntax and 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

'((2 3 4 5) (6 7))

> #'(y )

#<syntax:eval:6:0 (a b c)>

Since the trick is pulled off by a custom begin form, provided by subtemplate, it will not work as expected at the REPL unless you explicitly wrap the define and ellipses with a begin form, as done above. Within a module, however, this should work fine.

1.4 Ellipsis-preserving unsyntax

Racket’s syntax and template from syntax/parse/experimental/template both forget the current ellipsis position within an unsyntax form. This makes it difficult to perform simple changes to each element of a pattern variable under ellipses. syntax/parse/experimental/template provides template metafunctions, but they are unpractical for one-off small-scale alterations. With subtemplate, #,e and #,@e both preserve the current ellipsis position, meaning that uses of syntax, quasisyntax, template and so on within e will use the currently-focused portion of pattern variables under ellipses.

Examples:
> (require subtemplate/override racket/list)
> (define sd syntax->datum)
> (define/syntax-parse ((v ) ) #'((1 2 3 4) (5 6)))
> (sd #`(foo #,(+ v ) ))

'(foo 10 11)

; Quote, escape, re-quote, re-escape, re-quote:
> (sd #`(foo #,(cons (length (syntax->list #'(v )))
                 #`(#,(add1 (syntax-e #'v)) ))
         ))

'(foo (4 2 3 4 5) (2 6 7))

; Concise version of the above:
> (sd #`(foo (#,(length (v )) #,(add1 v) ) ))

'(foo (4 2 3 4 5) (2 6 7))

> (sd #`(foo #,(length (syntax->list #'(v ))) ))

'(foo 4 2)

> (sd #`(foo #,(length (list v )) ))

'(foo 4 2)

> (sd #`(foo (#,(add1 v) ) ))

'(foo (2 3 4 5) (6 7))

> (sd #`(foo #,(add1 v)  ))

'(foo 2 3 4 5 6 7)

> (sd #`(foo #,@(range v)  ))

'(foo 0 0 1 0 1 2 0 1 2 3 0 1 2 3 4 0 1 2 3 4 5)

It is still possible to get the traditional full-escape behaviour with #,,e instead of unsyntax, and #,@,e or #,,@e instead of unsyntax-splicing:

Examples:
> (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

'(10 100)

> v

'((1 2 3 4) (5 6))

> (sd #`(foo (x #,,#'(x )) ))

'(foo (10 (10 100)) (100 (10 100)))

> (sd #`(foo (x #,,(stx-map (λ (x) (add1 (syntax-e x))) #'(x ))) ))

'(foo (10 (11 101)) (100 (11 101)))

> (sd #`(foo (x #,,(list (list (add1 v) ) )) ))

'(foo (10 ((2 3 4 5) (6 7))) (100 ((2 3 4 5) (6 7))))

> (sd #`(foo (x #,,(((add1 v) ) )) ))

'(foo (10 ((2 3 4 5) (6 7))) (100 ((2 3 4 5) (6 7))))

> (sd #`(foo (x #,,(stx-map (λ (x) (length (syntax->list x)))
                            #'((v ) ))) ))

'(foo (10 (4 2)) (100 (4 2)))

> (sd #`(foo (x #,,((length (v )) )) ))

'(foo (10 (4 2)) (100 (4 2)))

> (sd #`(foo ((v ) #,,((length (v )) )) ))

'(foo ((1 2 3 4) (4 2)) ((5 6) (4 2)))

> (sd #`(foo (x #,,@((length (v )) )) ))

'(foo (10 4 2) (100 4 2))

> (sd #`(foo (x #,@,(range (length (x )))) ))

'(foo (10 0 1) (100 0 1))

> (sd #`(foo (v  #,,@((range (length (v ))) )) ))

'(foo (1 2 3 4 (0 1 2 3) (0 1)) (5 6 (0 1 2 3) (0 1)))

1.5 Splicing and conditional template elements

The splicing form ?@ as well as ?? should be familiar to users of syntax/parse/experimental/template. The 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)) )

'(10 3 11)

> (list (?? (?@ v )
            (string-length s)) )

'(1 2 3 4 3 5 6)

> (list 'x (?@@ '(y y y) (?? (?@ (list 'c v ))) ) 'z)

'(x y y y c 1 2 3 4 c 5 6 z)

> (list (?if s "string" "list of numbers") )

'("list of numbers" "string" "list of numbers")

> (?cond [k (list (?? (?@ 'there-was-a-keyword v )) )]
         [b (list (?? (?@ 'there-was-a-boolean (?? v s) )) )]
         [else (list (?? (?@ (?? i) v )) )])

'(there-was-a-keyword 1 2 3 4 there-was-a-keyword 5 6)

> (list (?attr k) (?attr b) (?attr i))

'(#t #f #f)

> (?? k b i 'none)

'#:a-keyword

The ?@@ splicing form performs two levels of unwrapping (it can be understood as a way to perform (?@ (append elements ))). The (?if condition true false) is a generalisation of ??, which accepts a condition template, and produces the true-template if there are no missing elements in the condition (in the sense of ~optional), and produces false otherwise. ?cond is a shorthand for a sequence of nested ?if forms, and (?attr a) returns a boolean indicating the presence of the attribute (it is a shorthand for (?if a #t #f)). Finally, ?? itself is not limited to two alternatives. When given a single alternative, ?? implicitly uses (?@), i.e. the empty splice, as the second alternative (this is the behaviour of the version from 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 not implicitly added as a last alternative when there are already two or more alternatives).

The ?if form is useful when one would want to write a ?? form, where the triggering condition should not appear in the left-hand-side of ??, 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)

'(1 2 3)

> (my-sort #:reverse 3 2 1)

'(3 2 1)

Note that ?@ and ?@@ 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 apply:

Examples:
> (require subtemplate/override racket/function)
> (define l '((1 2 3) (4 5 6)))
> (vector 'a (?@ l) 'c)

'#(a ((1 2 3) (4 5 6)) c)

> (+ 0 (?@@ (?@@ l)) 7)

28

> (vector 'a (?@@ (?@@ l)) 'c)

'#(a 1 2 3 4 5 6 c)

> (+ 0 (?@@ . l) 7)

28

> (vector 'a (?@@ . l) 'c)

'#(a 1 2 3 4 5 6 c)

> (map + . l)

'(5 7 9)

2 The main subtemplate module

The subtemplate module provides subtemplate, an alternative to syntax/parse’s template, which supports several convenience features:
  • When an identifier yᵢ is encountered in a template, it is automatically defined as a pattern variable containing temporary identifiers.

    This avoids the need to manually call generate-temporaries.

    The generated temporary identifiers will be based on a xᵢ pattern variable with the same subscript as yᵢ, and yᵢ will be nested at the same ellipsis depth as xᵢ.

    The identifiers xᵢ and yᵢ must end wit the same subscript, which must be a sequence of unicode subscript characters picked among ₐ ₑ ₕ ᵢ ⱼ ₖ ₗ ₘ ₙ ₒ ₚ ᵣ ₛ ₜ ᵤ ᵥ ₓ ᵦ ᵧ ᵨ ᵩ ᵪ. Alternatively, the subscript may be specified with an underscore followed by any characters other than an underscore. The two notations are equivalent, in the sense that yᵦ and y_β are interpreted in the same way, and if both appear within a template, they will use the same sequence of temporary identifiers generated from an xᵦ or x_β.

  • The value of pattern variables is automatically extracted when the variable does not appear in a syntax template. Note that since the syntax object is transformed into a plain datum, source locations and lexical contexts are lost. This is a trade-off between better error messages, which make sure that source locations and lexical context are not lost by accident (no automatic syntax-e), and more concise code (with automatic syntax-e). It is possible that a future version may require explicit syntax-e, possibly via a concise shorthand like unquote (,) or unsyntax (#,), if this feature turns out to be too dangerous in practice.

  • Ellipses work outside of syntax templates, and can be used after definitions and expressions.
    • The result of an expression under n ellipses is a \text{nested}^n list, where the expression is evaluated for each value of the pattern variables located within. In other words, (x ...) should produce a value similar to (syntax->datum #'(x ...)). However, it is possible to actually manipulate the value, e.g. by writing (+ x 1) .... It is possible to write m ellipses in a row (which has the effect of flattening m - 1 levels in the result list). It is also possible to nest the use of these ellipses, e.g. with (x ...) ..., which keeps the structure of the nested lists in the result.

    • When a definition form (define, define/with-syntax or define/syntax-parse for now) is followed by n ellipses, then the defined identifier is a \text{nested}^n list, or a syntax pattern variable with an ellipsis depth of n. The expression is evaluated for each value of the template variables it contains. Note that the structure of the nested lists is not flattened, despite the fact that the ellipses are written one after another. This is because it is usually the desired outcome, and nesting parentheses around the definition form would produce rather unreadable code.

    • These ellipses can also be used “inline” within function calls (subtemplate overrides #%app to achieve this). For example: (/ (+ x ...) (length x)) would compute the average of (syntax->datum #'(x ...))

    • Subscripted identifiers should also work in expressions (subtemplate overrides #%top to achieve this), although this seems less useful, as the temporary identifiers loose their lexical context information in that way.

    • The splicing forms ?@ and ?@@, as well as ??, ?if and ?cond work within expressions, and can be used to splice values into the argument list when calling a function. For example, (+ 1 (?@ l) 3) would splice the values of the list l into the argument list, effectively calling (+ 1 97 98 99 3) if l was equal to #'(97 98 99). Additionnally, it is possible to append a list at the end of the argument list, with the syntax (+ 1 2 . l).

    • It is possible to create a syntax object based on one of the iterated pattern variables within the expression-ellipses, for example using (#'x  ...).

  • Within a subtemplate and a quasisubtemplate, it is possible to use unsyntax and unsyntax-splicing to escape from the template. Within the escaped expression, the ellipsis depth of the template is conserved, making it possible to write (subtemplate (#,(+ x 1)  ...)), for example.

    The usual behaviour, which resets the ellipsis count to 0, can be obtained with #,,expr (that is, (unsyntax (unquote expr))) for an unsyntax-like escape. An unsyntax-splicing-style escape can be obtained with #,,@expr or #,@,expr (that is, (unsyntax (unquote-splicing expr)) or (unsyntax-splicing (unquote expr))).

  • Several utilities in the spirit of ?? and ?@ are provided, namely ?@@, ?attr ?cond and ?if.

  • All features (subscripted identifiers, dotted expressions and definitions, and the ellipsis-preserving unsyntax) should work well with omitted elements in attributes, as created by ~optional or ~or in syntax-parse.

2.1 Modules re-provided by subtemplate

The subtemplate library needs some cooperation from syntax-case, syntax-parse and similar forms. For this reason, some patched versions are defined in the stxparse-info library. subtemplate cannot work properly if the right modules are loaded. To make it easier to use subtemplate, it re-provides the modules that need to be loaded for it to function properly.

The subtemplate module re-provides stxparse-info/parse, stxparse-info/case and the parts of racket/syntax which are not overridden by stxparse-info/case.

The subtemplate/private/override module also re-provides stxparse-info/parse/experimental/template, but without template, quasitemplate, ?? and ?@, which are remapped to their equivalents from this library, and without template/loc] and quasitemplate/loc, which do not have an equivalent yet.

2.2 New and overridden bindings provided by subtemplate

syntax

(subtemplate tmpl)

(subtemplate tmpl #:properties (prop ...))
 
  prop : identifier?
Like template from syntax/parse/experimental/template, but automatically derives identifiers for any yᵢ which is not bound as a syntax pattern variable, based on a corresponding xᵢ which is bound as a syntax pattern variable. Additionally, subtemplate supports a number of features described in The main subtemplate module, which are not part of syntax/parse/experimental/template

syntax

(quasisubtemplate tmpl)

(quasisubtemplate tmpl #:properties (prop ...))
 
  prop : identifier?
Like quasitemplate from syntax/parse/experimental/template, but automatically derives identifiers for any yᵢ which is not bound as a syntax pattern variable, based on a corresponding xᵢ which is bound as a syntax pattern variable, in the same way as subtemplate. Additionally, quasisubtemplate supports a number of features described in The main subtemplate module, which are not part of syntax/parse/experimental/template

syntax

(template tmpl)

(template tmpl #:properties (prop ...))
 
  prop : identifier?
Like subtemplate, but does not automatically generate pattern variables based on their subscript. The other features still work (ellipsis-preserving escapes with unsyntax, support for ?@@, ?attr, ?cond and ?if).

syntax

(quasitemplate tmpl)

(quasitemplate tmpl #:properties (prop ...))
 
  prop : identifier?
Like quasisubtemplate, but does not automatically generate pattern variables based on their subscript. The other features still work (ellipsis-preserving escapes with unsyntax, support for ?@@, ?attr, ?cond and ?if).

procedure

(?@ . expr)

Splices the expr into the surrounding form (which must be a function application). If the surrounding form is a begin, let, or #%intdef-begin, then the the splicing lists are not processed, but may be processed later by using the splicing-list value as an argument to a function.

Also works in template, subtemplate and their derivatives.

procedure

(?@@ . expr)

Appends all the lists contained within expr, and splices the resulting list into the surrounding form. If the surrounding form is a begin, let, or #%intdef-begin, then the splicing lists are not processed, but may be processed later by using the splicing-list value as an argument to a function.

Also works in template, subtemplate and their derivatives.

syntax

(?? alt)

(?? alt ...+ else)
Executes alt, if none of the template variables within is omitted (i.e. bound to #false for the current ellipsis iteration). Otherwise, the next alt is considered. If every alt contains omitted template variables, then else is excuted. If only one alt is specified, without an else, then else defaults to (?@), i.e. the empty splice.

Also works in template, subtemplate and their derivatives.

syntax

(?if condition alt)

(?if condition alt else)
Generalisation of ??. If none of the template variables within condition is omitted (i.e. bound to #false for the current ellipsis iteration), then alt is executed. Otherwise, else is executed.

Also works in template, subtemplate and their derivatives.

syntax

(?attr condition)

Shorthand for ?if condition #t #f

Also works in template, subtemplate and their derivatives.

syntax

(?cond [condition alt] ...)

(?cond [condition alt] ... [else alt])
Equivalent to nested uses of ?if. If no else clause is supplied, then (?@), i.e. the empty splice, is used instead.

syntax

(begin body ...)

Overridden version of begin. Supports ellipses after definitions (using define, define/with-syntax or define/syntax-parse). Supports ellipses after expressions, in which case the results are grouped into a splicing list, which makes it possible to write (+ (begin x ...)) and obtain the same result as with (+ x ...).

Changed in version 1.2 of package subtemplate: Added support define/syntax-parse, fixed documentation which incorrectly claimed support for define-syntax instead of define/with-syntax

syntax

(let ([var val] ...) . body)

(let name ([var val] ...) . body)
Overridden version of let. Supports ellipses in the body after definitions (using define and define-syntax). Supports ellipses after expressions both in the body and in the val. In both cases, the results are grouped into a splicing list, which makes it possible to write (let ([vs x ...]) (+ vs)) and obtain the same result as with (+ x ...).

syntax

(#%intdef-begin . body)

Equivalent to begin from subtemplate, but assumes that it appears directly within the body of a let or similar form.

Third-party macros can cooperate with subtemplate, allowing its features to be used where a sequence of statements is expected. To achieve that, the macro would need to detect with identifier-binding and syntax-local-introduce whether #%intdef-begin is bound at the macro’s use-site. If this is the case, then the macro could use #%intdef-begin instead of begin.

syntax

(#%app f arg ... . rest)

(#%app val ooo ...+ expression ...+ . rest)
Overridden version of #%app, which supports ellipses in the argument list. When one of the arguments contains a splicing list, the list’s values are spliced into the argument list.

If the first argument is an ellipsis, the list function is implicitly used, and the first element following #%app is interpreted as an argument under ellipses.

A variable appearing in tail position after a dot is appended to the argument list, and splicing-lists within are handled.

syntax

(#%top . var)

Overridden version of #%top, which is used to automatically derive temporary identifiers in expressions. When an unbound variable yᵢ is used and a matching pattern variable xᵢ with the same subscript is bound. Note that if a variable yᵢ is already bound to some value, no attempt will be made to derive temporary identifiers for that variable. In contrast, if the identifier yᵢ appears, quoted by a subtemplate, then subtemplate will attempt to derive it even if it is bound (unless it is bound as a pattern variable).

syntax

Alias for ...

syntax

…+

Alias for ...+

3 Overriding the default #' and #`

The subtemplate/override module provides the same bindings as subtemplate, but also re-provides subtemplate as syntax, and quasisubtemplate as quasisyntax. This allows subtemplate to be used via the reader shorthands #' and #`.

4 Limitations

The derived subscripted identifiers have to be syntactically present within the template. In particular, if a template metafunction generates a part of a template containing yᵢ, it will work only if yᵢ is also present in the "main" part of the template (possibly as an argument to the template metafunction, or elsewhere).

Currently, template metafunctions defined with stxparse-info/parse/experimental/template are not compatible with those from syntax/parse/experimental/template, and vice versa. There is a pending pull request to make some level of compatibility possible, so this problem should hopefully be fixed sometime soon.

More generally, there might still be some incompatibilities between stxparse-info/parse and syntax/parse (aside from the fact that subtemplate cannot derive yᵢ from xᵢ if xᵢ was defined by the “official” syntax/parse), please report them to https://github.com/jsmaniac/subtemplate/issues.

The code generated by subtemplate is not optimised, so compile-time and run-time performance will not be as good as with syntax or template.

The expression splicing-lists are not recognised by templates, and it is not possible for a template to produce a “splicing syntax object” (instead, an error is raised if a ?@ causes a template to return more than one syntax object).

Despite the rather extensive test suite, there are likely still some bugs lurking, please report them to https://github.com/jsmaniac/subtemplate/issues.

4.1 Omitted elements in attributes (via ~optional)

When some values are missing in the ellipses of a template variable, e.g. via ~optional, subtemplate combines all the existing bound variables it can find with the correct subscript, in order to fill in as many elements of the derived variable. For example, if (attribute xᵢ)For readability reasons, we note '(x y) instead of (list #'x  #'y) here. returns '((a #f #f) #f (g h i) #f), and (attribute yᵢ) returns '(#f (4 5 6) (7 8 9) #f), then for a derived zᵢ , (attribute zᵢ) will contain '((a/z xᵢ79/z xᵢ80/z) (4/z 5/z 6/z) (g/z h/z i/z) #f). The last element is #f, as subtemplate lacks enough information to determine how many elements should be present within the list. The fully-nested #f in '(a #f #f) are derived, as it is clear at that point that there is place for only a single omitted element.

If new pattern variables with the same subscript are introduced after a generated variable was used, they should have the same structure (i.e. missing sublists in the same positions). Otherwise, the derived variable generated by subtemplate would not contain the same elements before and after that new pattern variable was introduced.

5 Lightweight Subtemplate

This module only provides stripped-down versions of subtemplate and quasisubtemplate, without overriding syntax and quasisyntax. Note that some features will not work when using these versions. Prefer using (require subtemplate) instead.
Another limitation is that subscripted identifiers are not searched for within unquoted parts of the template.
Note that you need to require stxparse-info/parse and stxparse-info/case, otherwise subtemplate and quasisubtemplate will not be able to detect which pattern variables are bound (and therefore will be unable to know from which xᵢ an yᵢ should be derived.

syntax

(subtemplate template)

(subtemplate template #:properties (prop ...))
 
  prop : identifier?
Like subtemplate from subtemplate, but with a few features missing (?@@ ?attr ?cond ?if).

syntax

(subtemplate template)

(subtemplate template #:properties (prop ...))
 
  prop : identifier?
Like subtemplate from subtemplate, but with a few features missing. The utilities ?@@ ?attr ?cond ?if are not taken into account, and unsyntax completely escapes the ellipses.

Note that the syntax pattern variables must be matched with one of the patched forms from stxparse-info/parse or stxparse-info/case, instead of the syntax pattern-matching forms from syntax/parse or racket/base, respectively.

syntax

(quasisubtemplate template)

(quasisubtemplate template #:properties (prop ...))
 
  prop : identifier?
Like subtemplate from subtemplate, but with a few features missing. The utilities ?@@ ?attr ?cond ?if are not taken into account, and unsyntax completely escapes the ellipses

Another limitation is that subscripted identifiers are not searched for within unquoted parts of the template.

Note that the syntax pattern variables must be matched with one of the patched forms from stxparse-info/parse or stxparse-info/case, instead of the syntax pattern-matching forms from syntax/parse or racket/base, respectively.