use defform #:grammar

This commit is contained in:
Ryan Culpepper 2013-03-20 21:49:37 -04:00
parent 293b208af7
commit 2eae24b0b1
5 changed files with 203 additions and 180 deletions

View File

@ -20,15 +20,16 @@ compatibility.
@defmodule[syntax/parse/experimental/provide] @defmodule[syntax/parse/experimental/provide]
@defform/subs[#:literals (syntax-class/c) @defform[#:literals (syntax-class/c)
(provide-syntax-class/contract (provide-syntax-class/contract
[syntax-class-id syntax-class-contract] ...) [syntax-class-id syntax-class-contract] ...)
([syntax-class-contract #:grammar
(syntax-class/c (mandatory-arg ...)) ([syntax-class-contract
(syntax-class/c (mandatory-arg ...) (syntax-class/c (mandatory-arg ...))
(optional-arg ...))] (syntax-class/c (mandatory-arg ...)
[arg contract-expr (code:line keyword contract-expr)]) (optional-arg ...))]
#:contracts ([contract-expr contract?])]{ [arg contract-expr (code:line keyword contract-expr)])
#:contracts ([contract-expr contract?])]{
Provides the syntax class (or splicing syntax class) Provides the syntax class (or splicing syntax class)
@racket[syntax-class-id] with the given contracts imposed on its @racket[syntax-class-id] with the given contracts imposed on its
@ -101,9 +102,10 @@ error is raised.
(~splicing-reflect var-id (reified-expr arg-expr ...) (~splicing-reflect var-id (reified-expr arg-expr ...)
maybe-attrs)]] maybe-attrs)]]
@specsubform/subs[(@#,(defhere ~reflect) var-id (reified-expr arg-expr ...) maybe-attrs) @specsubform[(@#,(defhere ~reflect) var-id (reified-expr arg-expr ...) maybe-attrs)
([maybe-attrs (code:line) #:grammar
(code:line #:attributes (attr-arity-decl ...))])]{ ([maybe-attrs (code:line)
(code:line #:attributes (attr-arity-decl ...))])]{
Like @racket[~var], except that the syntax class position is an Like @racket[~var], except that the syntax class position is an
expression evaluating to a reified syntax object, not a syntax class expression evaluating to a reified syntax object, not a syntax class
@ -189,9 +191,10 @@ sets of terms but also repetition constraints.
This module provides @deftech{ellipsis-head alternative sets}, This module provides @deftech{ellipsis-head alternative sets},
reusable encapsulations of @|EHpatterns|. reusable encapsulations of @|EHpatterns|.
@defform/subs[#:literals (pattern) @defform[#:literals (pattern)
(define-eh-alternative-set name eh-alternative ...) (define-eh-alternative-set name eh-alternative ...)
([alternative (pattern EH-pattern)])]{ #:grammar
([alternative (pattern EH-pattern)])]{
Defines @racket[name] as an ellipsis-head alternative set. Using Defines @racket[name] as an ellipsis-head alternative set. Using
@racket[name] (via @racket[~eh-var]) in an ellipsis-head pattern is @racket[name] (via @racket[~eh-var]) in an ellipsis-head pattern is
@ -246,11 +249,12 @@ their attributes with @racket[name].
@defmodule[syntax/parse/experimental/specialize] @defmodule[syntax/parse/experimental/specialize]
@defform/subs[(define-syntax-class/specialize header syntax-class-use) @defform[(define-syntax-class/specialize header syntax-class-use)
([header id #:grammar
(id . kw-formals)] ([header id
[syntax-class-use target-stxclass-id (id . kw-formals)]
(target-stxclass-id arg ...)])]{ [syntax-class-use target-stxclass-id
(target-stxclass-id arg ...)])]{
Defines @racket[id] as a syntax class with the same attributes, Defines @racket[id] as a syntax class with the same attributes,
options (eg, @racket[#:commit], @racket[#:no-delimit-cut]), and options (eg, @racket[#:commit], @racket[#:no-delimit-cut]), and
@ -272,22 +276,23 @@ patterns as @racket[target-stxclass-id] but with the given
@(define literal-ellipsis (racket ...)) @(define literal-ellipsis (racket ...))
@defform/subs[#:literals (?? ?@) @defform[#:literals (?? ?@)
(template tmpl) (template tmpl)
([tmpl pattern-variable-id #:grammar
(head-tmpl . tmpl) ([tmpl pattern-variable-id
(head-tmpl ellipsis ...+ . tmpl) (head-tmpl . tmpl)
(metafunction-id . tmpl) (head-tmpl ellipsis ...+ . tmpl)
(?? tmpl tmpl) (metafunction-id . tmpl)
#(@#,svar[head-tmpl] ...) (?? tmpl tmpl)
#s(prefab-struct-key @#,svar[head-tmpl] ...) #(@#,svar[head-tmpl] ...)
#&@#,svar[tmpl] #s(prefab-struct-key @#,svar[head-tmpl] ...)
constant-term] #&@#,svar[tmpl]
[head-templ tmpl constant-term]
(?? head-tmpl) [head-templ tmpl
(?? head-tmpl head-tmpl) (?? head-tmpl)
(?@ . tmpl)] (?? head-tmpl head-tmpl)
[ellipsis @#,literal-ellipsis])]{ (?@ . tmpl)]
[ellipsis @#,literal-ellipsis])]{
Constructs a syntax object from a syntax template, like Constructs a syntax object from a syntax template, like
@racket[syntax], but provides additional templating forms for dealing @racket[syntax], but provides additional templating forms for dealing

View File

@ -15,19 +15,20 @@ As a remedy, @racketmodname[syntax/parse] offers @deftech{literal
sets}. A literal set is defined via @racket[define-literal-set] and sets}. A literal set is defined via @racket[define-literal-set] and
used via the @racket[#:literal-set] option of @racket[syntax-parse]. used via the @racket[#:literal-set] option of @racket[syntax-parse].
@defform/subs[(define-literal-set id maybe-phase maybe-imports maybe-datum-literals @defform[(define-literal-set id maybe-phase maybe-imports maybe-datum-literals
(literal ...)) (literal ...))
([literal literal-id #:grammar
(pattern-id literal-id)] ([literal literal-id
[maybe-phase (code:line) (pattern-id literal-id)]
(code:line #:for-template) [maybe-phase (code:line)
(code:line #:for-syntax) (code:line #:for-template)
(code:line #:for-label) (code:line #:for-syntax)
(code:line #:phase phase-level)] (code:line #:for-label)
[maybe-datum-literals (code:line) (code:line #:phase phase-level)]
(code:line #:datum-literals (datum-literal ...))] [maybe-datum-literals (code:line)
[maybe-imports (code:line) (code:line #:datum-literals (datum-literal ...))]
(code:line #:literal-sets (imported-litset-id ...))])]{ [maybe-imports (code:line)
(code:line #:literal-sets (imported-litset-id ...))])]{
Defines @racket[id] as a @tech{literal set}. Each @racket[literal] can Defines @racket[id] as a @tech{literal set}. Each @racket[literal] can
have a separate @racket[pattern-id] and @racket[literal-id]. The have a separate @racket[pattern-id] and @racket[literal-id]. The
@ -114,12 +115,13 @@ the @racket[_phase] argument defaults to
] ]
} }
@defform/subs[(define-conventions name-id convention-rule ...) @defform[(define-conventions name-id convention-rule ...)
([convention-rule (name-pattern syntax-class)] #:grammar
[name-pattern exact-id ([convention-rule (name-pattern syntax-class)]
name-rx] [name-pattern exact-id
[syntax-class syntax-class-id name-rx]
(syntax-class-id expr ...)])]{ [syntax-class syntax-class-id
(syntax-class-id expr ...)])]{
Defines @deftech{conventions} that supply default syntax classes for Defines @deftech{conventions} that supply default syntax classes for
pattern variables. A pattern variable that has no explicit syntax pattern variables. A pattern variable that has no explicit syntax

View File

@ -20,27 +20,28 @@ of @tech{syntax patterns}, which is described in detail in
Two parsing forms are provided: @racket[syntax-parse] and Two parsing forms are provided: @racket[syntax-parse] and
@racket[syntax-parser]. @racket[syntax-parser].
@defform/subs[(syntax-parse stx-expr parse-option ... clause ...+) @defform[(syntax-parse stx-expr parse-option ... clause ...+)
([parse-option (code:line #:context context-expr) #:grammar
(code:line #:literals (literal ...)) ([parse-option (code:line #:context context-expr)
(code:line #:datum-literals (datum-literal ...)) (code:line #:literals (literal ...))
(code:line #:literal-sets (literal-set ...)) (code:line #:datum-literals (datum-literal ...))
(code:line #:conventions (convention-id ...)) (code:line #:literal-sets (literal-set ...))
(code:line #:local-conventions (convention-rule ...)) (code:line #:conventions (convention-id ...))
(code:line #:disable-colon-notation)] (code:line #:local-conventions (convention-rule ...))
[literal literal-id (code:line #:disable-colon-notation)]
(pattern-id literal-id) [literal literal-id
(pattern-id literal-id #:phase phase-expr)] (pattern-id literal-id)
[datum-literal literal-id (pattern-id literal-id #:phase phase-expr)]
(pattern-id literal-id)] [datum-literal literal-id
[literal-set literal-set-id (pattern-id literal-id)]
(literal-set-id literal-set-option ...)] [literal-set literal-set-id
[literal-set-option (code:line #:at context-id) (literal-set-id literal-set-option ...)]
(code:line #:phase phase-expr)] [literal-set-option (code:line #:at context-id)
[clause (syntax-pattern pattern-directive ... body ...+)]) (code:line #:phase phase-expr)]
#:contracts ([stx-expr syntax?] [clause (syntax-pattern pattern-directive ... body ...+)])
[context-expr syntax?] #:contracts ([stx-expr syntax?]
[phase-expr (or/c exact-integer? #f)])]{ [context-expr syntax?]
[phase-expr (or/c exact-integer? #f)])]{
Evaluates @racket[stx-expr], which should produce a syntax object, and Evaluates @racket[stx-expr], which should produce a syntax object, and
matches it against the @racket[clause]s in order. If some clause's matches it against the @racket[clause]s in order. If some clause's
@ -74,11 +75,12 @@ failures; otherwise @racket[stx-expr] is used. The
[(x:id ...) 'ok])) [(x:id ...) 'ok]))
} }
@specsubform/subs[(code:line #:literals (literal ...)) @specsubform[(code:line #:literals (literal ...))
([literal literal-id #:grammar
(pattern-id literal-id) ([literal literal-id
(pattern-id literal-id #:phase phase-expr)]) (pattern-id literal-id)
#:contracts ([phase-expr (or/c exact-integer? #f)])]{ (pattern-id literal-id #:phase phase-expr)])
#:contracts ([phase-expr (or/c exact-integer? #f)])]{
@margin-note*{ @margin-note*{
Unlike @racket[syntax-case], @racket[syntax-parse] requires all Unlike @racket[syntax-case], @racket[syntax-parse] requires all
@ -105,9 +107,10 @@ occurrence of @racket[pattern-id] were replaced with the following pattern:
@racketblock[(~literal literal-id #:phase phase-expr)] @racketblock[(~literal literal-id #:phase phase-expr)]
} }
@specsubform/subs[(code:line #:datum-literals (datum-literal ...)) @specsubform[(code:line #:datum-literals (datum-literal ...))
([datum-literal literal-id #:grammar
(pattern-id literal-id)])]{ ([datum-literal literal-id
(pattern-id literal-id)])]{
Like @racket[#:literals], but the literals are matched as symbols Like @racket[#:literals], but the literals are matched as symbols
instead of as identifiers. instead of as identifiers.
@ -118,12 +121,13 @@ pattern:
@racketblock[(~datum literal-id)] @racketblock[(~datum literal-id)]
} }
@specsubform/subs[(code:line #:literal-sets (literal-set ...)) @specsubform[(code:line #:literal-sets (literal-set ...))
([literal-set literal-set-id #:grammar
(literal-set-id literal-set-option ...)] ([literal-set literal-set-id
[literal-set-option (code:line #:at lctx) (literal-set-id literal-set-option ...)]
(code:line #:phase phase-expr)]) [literal-set-option (code:line #:at lctx)
#:contracts ([phase-expr (or/c exact-integer? #f)])]{ (code:line #:phase phase-expr)])
#:contracts ([phase-expr (or/c exact-integer? #f)])]{
Many literals can be declared at once via one or more @tech{literal Many literals can be declared at once via one or more @tech{literal
sets}, imported with the @racket[#:literal-sets] option. See sets}, imported with the @racket[#:literal-sets] option. See

View File

@ -260,12 +260,13 @@ like an @tech{annotated pattern variable} with the implicit syntax
class inserted. class inserted.
} }
@specsubform/subs[(@#,def[~var s+] pvar-id syntax-class-use maybe-role) @specsubform[(@#,def[~var s+] pvar-id syntax-class-use maybe-role)
([syntax-class-use syntax-class-id #:grammar
(syntax-class-id arg ...)] ([syntax-class-use syntax-class-id
[maybe-role (code:line) (syntax-class-id arg ...)]
(code:line #:role role-expr)]) [maybe-role (code:line)
#:contracts ([role-expr (or/c string? #f)])]{ (code:line #:role role-expr)])
#:contracts ([role-expr (or/c string? #f)])]{
An @deftech{annotated pattern variable}. The pattern matches only An @deftech{annotated pattern variable}. The pattern matches only
terms accepted by @svar[syntax-class-id] (parameterized by the terms accepted by @svar[syntax-class-id] (parameterized by the
@ -305,9 +306,10 @@ combined with the syntax class's description in error messages.
] ]
} }
@specsubform/subs[(@#,defhere[~literal] literal-id maybe-phase) @specsubform[(@#,defhere[~literal] literal-id maybe-phase)
([maybe-phase (code:line) #:grammar
(code:line #:phase phase-expr)])]{ ([maybe-phase (code:line)
(code:line #:phase phase-expr)])]{
A @deftech{literal} identifier pattern. Matches any identifier A @deftech{literal} identifier pattern. Matches any identifier
@racket[free-identifier=?] to @racket[literal-id]. @racket[free-identifier=?] to @racket[literal-id].
@ -557,13 +559,14 @@ above).
] ]
} }
@specsubform/subs[(@#,def[~describe s] maybe-opaque expr S-pattern) @specsubform[(@#,def[~describe s] maybe-opaque expr S-pattern)
([maybe-opaque (code:line) #:grammar
(code:line #:opaque)] ([maybe-opaque (code:line)
[maybe-role (code:line) (code:line #:opaque)]
(code:line #:role role-expr)]) [maybe-role (code:line)
#:contracts ([expr (or/c string? #f)] (code:line #:role role-expr)])
[role-expr (or/c string? #f)])]{ #:contracts ([expr (or/c string? #f)]
[role-expr (or/c string? #f)])]{
The @racket[~describe] pattern form annotates a pattern with a The @racket[~describe] pattern form annotates a pattern with a
description, a string expression that is evaluated in the scope of all description, a string expression that is evaluated in the scope of all
@ -647,12 +650,13 @@ Equivalent to @racket[(~var pvar-id splicing-syntax-class-id)].
} }
@specsubform/subs[(@#,def[~var h] pvar-id splicing-syntax-class-use maybe-role) @specsubform[(@#,def[~var h] pvar-id splicing-syntax-class-use maybe-role)
([splicing-syntax-class-use splicing-syntax-class-id #:grammar
(splicing-syntax-class-id arg ...)] ([splicing-syntax-class-use splicing-syntax-class-id
[maybe-role (code:line) (splicing-syntax-class-id arg ...)]
(code:line #:role role-expr)]) [maybe-role (code:line)
#:contracts ([role-expr (or/c string? #f)])]{ (code:line #:role role-expr)])
#:contracts ([role-expr (or/c string? #f)])]{
Pattern variable annotated with a @tech{splicing syntax Pattern variable annotated with a @tech{splicing syntax
class}. Similar to a normal @tech{annotated pattern variable}, except class}. Similar to a normal @tech{annotated pattern variable}, except
@ -721,13 +725,14 @@ terms instead.
] ]
} }
@specsubform/subs[(@#,def[~optional h] H-pattern maybe-optional-option) @specsubform[(@#,def[~optional h] H-pattern maybe-optional-option)
([maybe-optional-option #:grammar
(code:line) ([maybe-optional-option
(code:line #:defaults ([attr-arity-decl expr] ...))] (code:line)
[attr-arity-decl (code:line #:defaults ([attr-arity-decl expr] ...))]
attr-id [attr-arity-decl
(attr-id depth)])]{ attr-id
(attr-id depth)])]{
Matches either the given head subpattern or an empty sequence of Matches either the given head subpattern or an empty sequence of
terms. If the @racket[#:defaults] option is given, the subsequent terms. If the @racket[#:defaults] option is given, the subsequent
@ -847,13 +852,14 @@ Here are the variants of @elem{@EHpattern}:
Matches if any of the inner @racket[EH-pattern] alternatives match. Matches if any of the inner @racket[EH-pattern] alternatives match.
} }
@specsubform/subs[(@#,defhere[~once] H-pattern once-option ...) @specsubform[(@#,defhere[~once] H-pattern once-option ...)
([once-option (code:line #:name name-expr) #:grammar
(code:line #:too-few too-few-message-expr) ([once-option (code:line #:name name-expr)
(code:line #:too-many too-many-message-expr)]) (code:line #:too-few too-few-message-expr)
#:contracts ([name-expr (or/c string? #f)] (code:line #:too-many too-many-message-expr)])
[too-few-message-expr (or/c string? #f)] #:contracts ([name-expr (or/c string? #f)]
[too-many-message-expr (or/c string? #f)])]{ [too-few-message-expr (or/c string? #f)]
[too-many-message-expr (or/c string? #f)])]{
Matches if the inner @racket[H-pattern] matches. This pattern must be Matches if the inner @racket[H-pattern] matches. This pattern must be
matched exactly once in the match of the entire repetition sequence. matched exactly once in the match of the entire repetition sequence.
@ -869,12 +875,13 @@ then the ellipsis pattern fails with the message either
of @racket[name-expr]"}. of @racket[name-expr]"}.
} }
@specsubform/subs[(@#,def[~optional eh] H-pattern optional-option ...) @specsubform[(@#,def[~optional eh] H-pattern optional-option ...)
([optional-option (code:line #:name name-expr) #:grammar
(code:line #:too-many too-many-message-expr) ([optional-option (code:line #:name name-expr)
(code:line #:defaults ([attr-id expr] ...))]) (code:line #:too-many too-many-message-expr)
#:contracts ([name-expr (or/c string? #f)] (code:line #:defaults ([attr-id expr] ...))])
[too-many-message-expr (or/c string? #f)])]{ #:contracts ([name-expr (or/c string? #f)]
[too-many-message-expr (or/c string? #f)])]{
Matches if the inner @racket[H-pattern] matches. This pattern may be used at Matches if the inner @racket[H-pattern] matches. This pattern may be used at
most once in the match of the entire repetition. most once in the match of the entire repetition.
@ -890,12 +897,13 @@ sequence. The default attributes must be a subset of the subpattern's
attributes. attributes.
} }
@specsubform/subs[(@#,defhere[~between] H-pattern min-number max-number between-option ...) @specsubform[(@#,defhere[~between] H-pattern min-number max-number between-option ...)
([reps-option (code:line #:name name-expr) #:grammar
(code:line #:too-few too-few-message-expr) ([reps-option (code:line #:name name-expr)
(code:line #:too-many too-many-message-expr)]) (code:line #:too-few too-few-message-expr)
#:contracts ([name-expr (or/c syntax? #f)] (code:line #:too-many too-many-message-expr)])
[too-few-message-expr (or/c syntax? #f)])]{ #:contracts ([name-expr (or/c syntax? #f)]
[too-few-message-expr (or/c syntax? #f)])]{
Matches if the inner @racket[H-pattern] matches. This pattern must be Matches if the inner @racket[H-pattern] matches. This pattern must be
matched at least @racket[min-number] and at most @racket[max-number] matched at least @racket[min-number] and at most @racket[max-number]
@ -966,22 +974,23 @@ within a @racket[~not] pattern unless there is an intervening
@racket[~delimit-cut] or @racket[~commit] pattern. @racket[~delimit-cut] or @racket[~commit] pattern.
} }
@specsubform/subs[(@#,defhere[~bind] [attr-arity-decl expr] ...) @specsubform[(@#,defhere[~bind] [attr-arity-decl expr] ...)
([attr-arity-decl #:grammar
attr-name-id ([attr-arity-decl attr-name-id
(attr-name-id depth)])]{ (attr-name-id depth)])]{
Evaluates the @racket[expr]s and binds them to the given Evaluates the @racket[expr]s and binds them to the given
@racket[attr-id]s as attributes. @racket[attr-id]s as attributes.
} }
@specsubform/subs[(@#,defhere[~fail] maybe-fail-condition maybe-message-expr) @specsubform[(@#,defhere[~fail] maybe-fail-condition maybe-message-expr)
([maybe-fail-condition (code:line) #:grammar
(code:line #:when condition-expr) ([maybe-fail-condition (code:line)
(code:line #:unless condition-expr)] (code:line #:when condition-expr)
[maybe-message-expr (code:line) (code:line #:unless condition-expr)]
(code:line message-expr)]) [maybe-message-expr (code:line)
#:contracts ([message-expr (or/c string? #f)])]{ (code:line message-expr)])
#:contracts ([message-expr (or/c string? #f)])]{
If the condition is absent, or if the @racket[#:when] condition If the condition is absent, or if the @racket[#:when] condition
evaluates to a true value, or if the @racket[#:unless] condition evaluates to a true value, or if the @racket[#:unless] condition

View File

@ -17,29 +17,30 @@ complex syntax, such as lists of distinct identifiers and formal
arguments with keywords. Macros that manipulate the same syntactic arguments with keywords. Macros that manipulate the same syntactic
structures can share syntax class definitions. structures can share syntax class definitions.
@defform*/subs[#:literals (pattern) @defform*[#:literals (pattern)
[(define-syntax-class name-id stxclass-option ... [(define-syntax-class name-id stxclass-option ...
stxclass-variant ...+) stxclass-variant ...+)
(define-syntax-class (name-id . kw-formals) stxclass-option ... (define-syntax-class (name-id . kw-formals) stxclass-option ...
stxclass-variant ...+)] stxclass-variant ...+)]
([stxclass-option #:grammar
(code:line #:attributes (attr-arity-decl ...)) ([stxclass-option
(code:line #:description description-expr) (code:line #:attributes (attr-arity-decl ...))
(code:line #:opaque) (code:line #:description description-expr)
(code:line #:commit) (code:line #:opaque)
(code:line #:no-delimit-cut) (code:line #:commit)
(code:line #:literals (literal-entry ...)) (code:line #:no-delimit-cut)
(code:line #:datum-literals (datum-literal-entry ...)) (code:line #:literals (literal-entry ...))
(code:line #:literal-sets (literal-set ...)) (code:line #:datum-literals (datum-literal-entry ...))
(code:line #:conventions (convention-id ...)) (code:line #:literal-sets (literal-set ...))
(code:line #:local-conventions (convention-rule ...)) (code:line #:conventions (convention-id ...))
(code:line #:disable-colon-notation)] (code:line #:local-conventions (convention-rule ...))
[attr-arity-decl (code:line #:disable-colon-notation)]
attr-name-id [attr-arity-decl
(attr-name-id depth)] attr-name-id
[stxclass-variant (attr-name-id depth)]
(pattern syntax-pattern pattern-directive ...)]) [stxclass-variant
#:contracts ([description-expr (or/c string? #f)])]{ (pattern syntax-pattern pattern-directive ...)])
#:contracts ([description-expr (or/c string? #f)])]{
Defines @racket[name-id] as a @deftech{syntax class}, which Defines @racket[name-id] as a @deftech{syntax class}, which
encapsulates one or more @tech{single-term patterns}. encapsulates one or more @tech{single-term patterns}.
@ -52,9 +53,10 @@ non-empty sequence of @racket[pattern] variants.
The following options are supported: The following options are supported:
@specsubform/subs[(code:line #:attributes (attr-arity-decl ...)) @specsubform[(code:line #:attributes (attr-arity-decl ...))
([attr-arity-decl attr-id #:grammar
(attr-id depth)])]{ ([attr-arity-decl attr-id
(attr-id depth)])]{
Declares the attributes of the syntax class. An attribute arity Declares the attributes of the syntax class. An attribute arity
declaration consists of the attribute name and optionally its ellipsis declaration consists of the attribute name and optionally its ellipsis
@ -181,11 +183,12 @@ follows:
(code:line #:when condition-expr) (code:line #:when condition-expr)
(code:line #:do [def-or-expr ...])] (code:line #:do [def-or-expr ...])]
@specsubform/subs[(code:line #:declare pvar-id stxclass maybe-role) @specsubform[(code:line #:declare pvar-id stxclass maybe-role)
([stxclass syntax-class-id #:grammar
(syntax-class-id arg ...)] ([stxclass syntax-class-id
[maybe-role (code:line) (syntax-class-id arg ...)]
(code:line #:role role-expr)])]{ [maybe-role (code:line)
(code:line #:role role-expr)])]{
Associates @racket[pvar-id] with a syntax class and possibly a role, Associates @racket[pvar-id] with a syntax class and possibly a role,
equivalent to replacing each occurrence of @racket[pvar-id] in the equivalent to replacing each occurrence of @racket[pvar-id] in the