add documentation for datum and syntax variables, attributes
This commit is contained in:
parent
07f9b843a6
commit
6f11f1f527
|
@ -2,7 +2,8 @@
|
||||||
@(require "common.rkt"
|
@(require "common.rkt"
|
||||||
scribble/eval
|
scribble/eval
|
||||||
(for-label racket/base
|
(for-label racket/base
|
||||||
syntax/datum))
|
syntax/datum
|
||||||
|
syntax/parse))
|
||||||
|
|
||||||
@(define datum-eval (make-base-eval))
|
@(define datum-eval (make-base-eval))
|
||||||
@interaction-eval[#:eval datum-eval (require syntax/datum)]
|
@interaction-eval[#:eval datum-eval (require syntax/datum)]
|
||||||
|
@ -32,23 +33,65 @@ in @racket[datum-case] should produce a @tech[#:doc refman]{datum}
|
||||||
(i.e., plain S-expression) instead of a @tech[#:doc refman]{syntax
|
(i.e., plain S-expression) instead of a @tech[#:doc refman]{syntax
|
||||||
object} to be matched in @racket[clause]s, and @racket[datum]
|
object} to be matched in @racket[clause]s, and @racket[datum]
|
||||||
similarly produces a datum. Pattern variables bound in each
|
similarly produces a datum. Pattern variables bound in each
|
||||||
@racket[clause] of @racket[datum-case] are accessible via
|
@racket[clause] of @racket[datum-case] (or @racket[syntax-case], see
|
||||||
@racket[datum] instead of @racket[syntax]. When a @racket[literal-id]
|
below) are accessible via @racket[datum] instead of
|
||||||
appears in a @racket[clause]'s pattern, it matches the corresponding
|
@racket[syntax]. When a @racket[literal-id] appears in a
|
||||||
symbol (using @racket[eq?]).
|
@racket[clause]'s pattern, it matches the corresponding symbol (using
|
||||||
|
@racket[eq?]).
|
||||||
|
|
||||||
|
Using @racket[datum-case] and @racket[datum] is similar
|
||||||
Using @racket[datum-case] and @racket[datum] is essentially equivalent
|
|
||||||
to converting the input to @racket[syntax-case] using
|
to converting the input to @racket[syntax-case] using
|
||||||
@racket[datum->syntax] and then wrapping each use of @racket[syntax]
|
@racket[datum->syntax] and then wrapping each use of @racket[syntax]
|
||||||
with @racket[syntax->datum], but @racket[datum-case] and
|
with @racket[syntax->datum], but @racket[datum-case] and
|
||||||
@racket[datum] to not create intermediate syntax objects.
|
@racket[datum] do not create intermediate syntax objects, and they do
|
||||||
|
not destroy existing syntax objects within the S-expression structure
|
||||||
|
of @racket[datum-expr].
|
||||||
|
|
||||||
@examples[
|
@examples[
|
||||||
#:eval datum-eval
|
#:eval datum-eval
|
||||||
(datum-case '(1 "x" -> y) (->)
|
(datum-case '(1 "x" -> y) (->)
|
||||||
[(a ... -> b) (datum (b (+ a) ...))])
|
[(a ... -> b) (datum (b (+ a) ...))])
|
||||||
]}
|
]
|
||||||
|
|
||||||
|
The @racket[datum] form also cooperates with @tech[#:key "pattern
|
||||||
|
variable" #:doc '(lib "scribblings/reference/reference.scrbl")]{syntax
|
||||||
|
pattern variables} such as those bound by @racket[syntax-case] and
|
||||||
|
@tech{attributes} bound by @racket[syntax-parse] (see
|
||||||
|
@secref["stxparse-attrs"] for more information about attributes). As
|
||||||
|
one consequence, @racket[datum] provides a convenient way of getting
|
||||||
|
the list of syntax objects bound to a syntax pattern variable of depth
|
||||||
|
1. For example, the following expressions are equivalent, except that
|
||||||
|
the @racket[datum] version avoids creating and eliminating a
|
||||||
|
superfluous syntax object wrapper:
|
||||||
|
|
||||||
|
@interaction[#:eval datum-eval
|
||||||
|
(with-syntax ([(x ...) #'(a b c)])
|
||||||
|
(syntax->list #'(x ...)))
|
||||||
|
(with-syntax ([(x ...) #'(a b c)])
|
||||||
|
(datum (x ...)))
|
||||||
|
]
|
||||||
|
|
||||||
|
A template can also use multiple syntax or datum pattern variables and
|
||||||
|
datum constants, and it can use the @racket[~@] and @racket[~?]
|
||||||
|
template forms:
|
||||||
|
|
||||||
|
@interaction[#:eval datum-eval
|
||||||
|
(with-syntax ([(x ...) #'(a b c)])
|
||||||
|
(with-datum ([(y ...) (list 1 2 3)])
|
||||||
|
(datum ([x -> y] ...))))
|
||||||
|
(with-syntax ([(x ...) #'(a b c)])
|
||||||
|
(with-datum ([(y ...) (list 1 2 3)])
|
||||||
|
(datum ((~@ x y) ...))))
|
||||||
|
]
|
||||||
|
|
||||||
|
See @secref["attributes-and-datum"] for examples of @racket[~?] with
|
||||||
|
@racket[datum].
|
||||||
|
|
||||||
|
If a datum variable is used in a syntax template, a compile-time error
|
||||||
|
is raised.
|
||||||
|
|
||||||
|
@history[#:changed "7.8.0.9" @elem{Changed @racket[datum] to
|
||||||
|
cooperate with @racket[syntax-case], @racket[syntax-parse], etc.}]}
|
||||||
|
|
||||||
|
|
||||||
@defform[(with-datum ([pattern datum-expr] ...)
|
@defform[(with-datum ([pattern datum-expr] ...)
|
||||||
|
|
|
@ -4,9 +4,11 @@
|
||||||
scribble/decode
|
scribble/decode
|
||||||
scribble/eval
|
scribble/eval
|
||||||
"parse-common.rkt"
|
"parse-common.rkt"
|
||||||
|
(for-label syntax/datum)
|
||||||
(for-syntax racket/base))
|
(for-syntax racket/base))
|
||||||
|
|
||||||
@(define the-eval (make-sp-eval))
|
@(define the-eval (make-sp-eval))
|
||||||
|
@(the-eval '(require syntax/datum))
|
||||||
|
|
||||||
@(define-syntax sub-kw-form
|
@(define-syntax sub-kw-form
|
||||||
(lambda (stx)
|
(lambda (stx)
|
||||||
|
@ -192,6 +194,28 @@ including nested attributes produced by syntax classes associated with
|
||||||
the pattern variables.
|
the pattern variables.
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
|
@defidform[this-syntax]{
|
||||||
|
|
||||||
|
When used as an expression within a syntax-class definition or
|
||||||
|
@racket[syntax-parse] expression, evaluates to the syntax object or
|
||||||
|
@tech[#:doc '(lib "scribblings/reference/reference.scrbl")]{syntax
|
||||||
|
pair} being matched.
|
||||||
|
|
||||||
|
@examples[#:eval the-eval
|
||||||
|
(define-syntax-class one (pattern _ #:attr s this-syntax))
|
||||||
|
(syntax-parse #'(1 2 3) [(1 o:one _) (attribute o.s)])
|
||||||
|
(syntax-parse #'(1 2 3) [(1 . o:one) (attribute o.s)])
|
||||||
|
(define-splicing-syntax-class two (pattern (~seq _ _) #:attr s this-syntax))
|
||||||
|
(syntax-parse #'(1 2 3) [(t:two 3) (attribute t.s)])
|
||||||
|
(syntax-parse #'(1 2 3) [(1 t:two) (attribute t.s)])
|
||||||
|
]
|
||||||
|
|
||||||
|
Raises an error when used as an expression outside of a syntax-class
|
||||||
|
definition or @racket[syntax-parse] expression.
|
||||||
|
}
|
||||||
|
|
||||||
|
|
||||||
@defthing[prop:syntax-class (struct-type-property/c (or/c identifier?
|
@defthing[prop:syntax-class (struct-type-property/c (or/c identifier?
|
||||||
(-> any/c identifier?)))]{
|
(-> any/c identifier?)))]{
|
||||||
|
|
||||||
|
@ -484,28 +508,34 @@ variable}. The name of a nested attribute is computed by concatenating
|
||||||
the pattern variable name with the syntax class's exported attribute's
|
the pattern variable name with the syntax class's exported attribute's
|
||||||
name, separated by a dot (see the example below).
|
name, separated by a dot (see the example below).
|
||||||
|
|
||||||
Attributes can be used in two ways: with the @racket[attribute] form,
|
Attributes can be used in three ways: with the @racket[attribute]
|
||||||
and inside syntax templates via @racket[syntax], @racket[quasisyntax],
|
form; inside syntax templates via @racket[syntax],
|
||||||
etc. Attribute names cannot be used directly as expressions; that is,
|
@racket[quasisyntax], etc; and inside @racket[datum]
|
||||||
attributes are not variables.
|
templates. Attribute names cannot be used directly as expressions;
|
||||||
|
that is, attributes are not variables.
|
||||||
|
|
||||||
A @deftech{syntax-valued attribute} is an attribute whose value is a
|
A @deftech{syntax-valued attribute} is an attribute whose value is a
|
||||||
syntax object, a syntax list of the appropriate @tech{ellipsis depth},
|
syntax object or list of the appropriate @tech{ellipsis depth}. That
|
||||||
or a tree containing @tech[#:doc '(lib
|
is, an attribute with ellipsis depth 0 is syntax-valued if its value
|
||||||
|
is @racket[syntax?]; an attribute with ellipis depth 1 is
|
||||||
|
syntax-valued if its value is @racket[(listof syntax?)]; an attribute
|
||||||
|
with ellipsis depth 2 is syntax-valued if its value is @racket[(listof
|
||||||
|
(listof syntax?))]; and so on. The value is considered syntax-valued
|
||||||
|
if it contains @tech[#:doc '(lib
|
||||||
"scribblings/reference/reference.scrbl")]{promises} that when
|
"scribblings/reference/reference.scrbl")]{promises} that when
|
||||||
completely forced produces a suitable syntax object or syntax
|
completely forced produces a suitable syntax object or
|
||||||
list. Syntax-valued attributes can be used within @racket[syntax],
|
list. Syntax-valued attributes can be used within @racket[syntax],
|
||||||
@racket[quasisyntax], etc as part of a syntax template. If an
|
@racket[quasisyntax], etc as part of a syntax template. If an
|
||||||
attribute is used inside a syntax template but it is not
|
attribute is used inside a syntax template but it is not
|
||||||
syntax-valued, an error is signaled.
|
syntax-valued, an error is signaled.
|
||||||
|
|
||||||
The value of an attribute is not required to be syntax.
|
There are uses for non-syntax-valued attributes. A non-syntax-valued
|
||||||
Non-syntax-valued attributes can be used to return a parsed
|
attribute can be used to return a parsed representation of a subterm
|
||||||
representation of a subterm or the results of an analysis on the
|
or the results of an analysis on the subterm. A non-syntax-valued
|
||||||
subterm. A non-syntax-valued attribute should be bound using the
|
attribute must be bound using the @racket[#:attr] directive or a
|
||||||
@racket[#:attr] directive or a @racket[~bind] pattern; @racket[#:with]
|
@racket[~bind] pattern; @racket[#:with] and @racket[~parse] will
|
||||||
and @racket[~parse] will convert the right-hand side to a (possibly
|
convert the right-hand side to a (possibly @tech[#:key "3d
|
||||||
3D) syntax object.
|
syntax"]{3D}) syntax object.
|
||||||
|
|
||||||
@examples[#:eval the-eval
|
@examples[#:eval the-eval
|
||||||
(define-syntax-class table
|
(define-syntax-class table
|
||||||
|
@ -525,10 +555,10 @@ and @racket[~parse] will convert the right-hand side to a (possibly
|
||||||
The @racket[table] syntax class provides four attributes:
|
The @racket[table] syntax class provides four attributes:
|
||||||
@racket[key], @racket[value], @racket[hashtable], and
|
@racket[key], @racket[value], @racket[hashtable], and
|
||||||
@racket[sorted-kv]. The @racket[hashtable] attribute has
|
@racket[sorted-kv]. The @racket[hashtable] attribute has
|
||||||
@tech{ellipsis depth} 0 and the rest have depth 1; all but
|
@tech{ellipsis depth} 0 and the rest have depth 1; @racket[key],
|
||||||
@racket[hashtable] are syntax-valued. The @racket[sorted-kv]
|
@racket[value], and @racket[sorted-kv] are syntax-valued, but
|
||||||
attribute's value is a promise; it will be automatically forced if
|
@racket[hashtable] is not. The @racket[sorted-kv] attribute's value is
|
||||||
used in a syntax template.
|
a promise; it will be automatically forced if used in a template.
|
||||||
|
|
||||||
Syntax-valued attributes can be used in syntax templates:
|
Syntax-valued attributes can be used in syntax templates:
|
||||||
|
|
||||||
|
@ -548,8 +578,8 @@ But non-syntax-valued attributes cannot:
|
||||||
#'t.hashtable])
|
#'t.hashtable])
|
||||||
]
|
]
|
||||||
|
|
||||||
Use the @racket[attribute] form to get the value of an attribute
|
The @racket[attribute] form gets the value of an attribute, whether it
|
||||||
(syntax-valued or not).
|
is syntax-valued or not.
|
||||||
|
|
||||||
@interaction[#:eval the-eval
|
@interaction[#:eval the-eval
|
||||||
(syntax-parse #'((a 1) (b 2) (c 3))
|
(syntax-parse #'((a 1) (b 2) (c 3))
|
||||||
|
@ -589,10 +619,10 @@ binds the following nested attributes: @racket[y.a] at depth 2,
|
||||||
depth 1.
|
depth 1.
|
||||||
|
|
||||||
An attribute's ellipsis nesting depth is @emph{not} a guarantee that
|
An attribute's ellipsis nesting depth is @emph{not} a guarantee that
|
||||||
it is syntax-valued. In particular, @racket[~or*] and
|
it is syntax-valued or has any list structure. In particular,
|
||||||
@racket[~optional] patterns may result in attributes with fewer than
|
@racket[~or*] and @racket[~optional] patterns may result in attributes
|
||||||
expected levels of list nesting, and @racket[#:attr] and
|
with fewer than expected levels of list nesting, and @racket[#:attr]
|
||||||
@racket[~bind] can be used to bind attributes to arbitrary values.
|
and @racket[~bind] can be used to bind attributes to arbitrary values.
|
||||||
|
|
||||||
@examples[#:eval the-eval
|
@examples[#:eval the-eval
|
||||||
(syntax-parse #'(a b 3)
|
(syntax-parse #'(a b 3)
|
||||||
|
@ -603,27 +633,77 @@ expected levels of list nesting, and @racket[#:attr] and
|
||||||
@defform[(attribute attr-id)]{
|
@defform[(attribute attr-id)]{
|
||||||
|
|
||||||
Returns the value associated with the @tech{attribute} named
|
Returns the value associated with the @tech{attribute} named
|
||||||
@racket[attr-id]. If @racket[attr-id] is not bound as an attribute, an
|
@racket[attr-id]. If @racket[attr-id] is not bound as an attribute, a
|
||||||
error is raised.
|
syntax error is raised.
|
||||||
}
|
}
|
||||||
|
|
||||||
@defidform[this-syntax]{
|
|
||||||
|
|
||||||
When used as an expression within a syntax-class definition or
|
@subsection[#:tag "attributes-and-datum"]{Attributes and @racket[datum]}
|
||||||
@racket[syntax-parse] expression, evaluates to the syntax object or
|
|
||||||
@tech[#:doc '(lib "scribblings/reference/reference.scrbl")]{syntax
|
|
||||||
pair} being matched.
|
|
||||||
|
|
||||||
@examples[#:eval the-eval
|
The @racket[datum] form is another way, in addition to @racket[syntax]
|
||||||
(define-syntax-class one (pattern _ #:attr s this-syntax))
|
and @racket[attribute], of using syntax pattern variables and
|
||||||
(syntax-parse #'(1 2 3) [(1 o:one _) (attribute o.s)])
|
attributes. Unlike @racket[syntax], @racket[datum] does not require
|
||||||
(syntax-parse #'(1 2 3) [(1 . o:one) (attribute o.s)])
|
attributes to be syntax-valued. Wherever the @racket[syntax] form
|
||||||
(define-splicing-syntax-class two (pattern (~seq _ _) #:attr s this-syntax))
|
would create syntax objects based on its template (as opposed to
|
||||||
(syntax-parse #'(1 2 3) [(t:two 3) (attribute t.s)])
|
reusing syntax objects bound by pattern variables), the @racket[datum]
|
||||||
(syntax-parse #'(1 2 3) [(1 t:two) (attribute t.s)])
|
form creates plain S-expressions.
|
||||||
]}
|
|
||||||
|
|
||||||
Raises an error when used as an expression outside of a syntax-class
|
Continuing the @racket[table] example from above, we can use
|
||||||
definition or @racket[syntax-parse] expression.
|
@racket[datum] with the @racket[key] attribute as follows:
|
||||||
|
|
||||||
|
@interaction[#:eval the-eval
|
||||||
|
(syntax-parse #'((a 1) (b 2) (c 3))
|
||||||
|
[t:table (datum (t.key ...))])
|
||||||
|
]
|
||||||
|
|
||||||
|
A @racket[datum] template may contain multiple pattern variables
|
||||||
|
combined within some S-expression structure:
|
||||||
|
|
||||||
|
@interaction[#:eval the-eval
|
||||||
|
(syntax-parse #'((a 1) (b 2) (c 3))
|
||||||
|
[t:table (datum ([t.key t.value] ...))])
|
||||||
|
]
|
||||||
|
|
||||||
|
A @racket[datum] template can use the @racket[~@] and @racket[~?]
|
||||||
|
template forms:
|
||||||
|
|
||||||
|
@interaction[#:eval the-eval
|
||||||
|
(syntax-parse #'((a 1) (b 2) (c 3))
|
||||||
|
[t:table (datum ((~@ t.key t.value) ...))])
|
||||||
|
(syntax-parse #'((a 56) (b 71) (c 13))
|
||||||
|
[t:table (datum ((~@ . t.sorted-kv) ...))])
|
||||||
|
(syntax-parse #'( ((a 1) (b 2) (c 3)) ((d 4) (e 5)) )
|
||||||
|
[(t1:table (~or* t2:table #:nothing))
|
||||||
|
(datum (t1.key ... (~? (~@ t2.key ...))))])
|
||||||
|
(syntax-parse #'( ((a 1) (b 2) (c 3)) #:nothing )
|
||||||
|
[(t1:table (~or* t2:table #:nothing))
|
||||||
|
(datum (t1.key ... (~? (~@ t2.key ...))))])
|
||||||
|
]
|
||||||
|
|
||||||
|
However, unlike for @racket[syntax], a value of @racket[#f] only
|
||||||
|
signals a template failure to @racket[~?] if a list is needed for
|
||||||
|
ellipsis iteration, as in the previous example; it does not cause a
|
||||||
|
failure when it occurs as a leaf. Contrast the following:
|
||||||
|
|
||||||
|
@interaction[#:eval the-eval
|
||||||
|
(syntax-parse #'( ((a 1) (b 2) (c 3)) #:nothing )
|
||||||
|
[(t1:table (~or* t2:table #:nothing))
|
||||||
|
#'(~? t2 skipped)])
|
||||||
|
(syntax-parse #'( ((a 1) (b 2) (c 3)) #:nothing )
|
||||||
|
[(t1:table (~or* t2:table #:nothing))
|
||||||
|
(datum (~? t2 skipped))])
|
||||||
|
]
|
||||||
|
|
||||||
|
The @racket[datum] form is also useful for accessing non-syntax-valued
|
||||||
|
attributes. Compared to @racket[attribute], @racket[datum] has the
|
||||||
|
following advantage: The use of ellipses in @racket[datum] templates
|
||||||
|
provides a visual reminder of the list structure of their results. For
|
||||||
|
example, if the pattern is @racket[(t:table ...)], then both
|
||||||
|
@racket[(attribute t.hashtable)] and @racket[(datum (t.hashtable
|
||||||
|
...))] produce a @racket[(listof hash?)], but the ellipses make it
|
||||||
|
more apparent.
|
||||||
|
|
||||||
|
@history[#:changed "7.8.0.9" @elem{Added support for syntax pattern
|
||||||
|
variables and attributes to @racket[datum].}]
|
||||||
|
|
||||||
@(close-eval the-eval)
|
@(close-eval the-eval)
|
||||||
|
|
Loading…
Reference in New Issue
Block a user