bkyk8rc3zvpnsf5inmcqq4n3k98cv6hj-my-site-hyper-literate-git.test.suzanne.soy-0.0.1

Unnamed repository; edit this file 'description' to name the repository.
Log | Files | Refs | README | LICENSE

reader-internals.scrbl (13106B)


      1 #lang scribble/doc
      2 @(require scribble/manual scribble/bnf scribble/eval "utils.rkt"
      3           (for-syntax racket/base)
      4           (for-label (only-in scribble/reader
      5                               use-at-readtable)))
      6 
      7 @(define read-eval (make-base-eval))
      8 @(interaction-eval #:eval read-eval (require (for-syntax racket/base)))
      9 
     10 @title[#:tag "reader-internals"]{@"@" Reader Internals}
     11 
     12 @;--------------------------------------------------------------------
     13 @section{Using the @"@" Reader}
     14 
     15 You can use the reader via Racket's @racketfont{#reader} form:
     16 
     17 @racketblock[
     18  @#,racketfont|{
     19      #reader scribble/reader @foo{This is free-form text!}
     20 }|]
     21 
     22 or use the @racket[at-exp] meta-language as described in
     23 @secref["at-exp-lang"].
     24 
     25 Note that the Scribble reader reads @tech{@"@"-forms} as S-expressions.  This
     26 means that it is up to you to give meanings for these expressions in
     27 the usual way: use Racket functions, define your functions, or require
     28 functions.  For example, typing the above into @exec{racket} is likely
     29 going to produce a ``reference to undefined identifier'' error, unless
     30 @racket[foo] is defined. You can use @racket[string-append] instead,
     31 or you can define @racket[foo] as a function (with variable arity).
     32 
     33 A common use of the Scribble @"@"-reader is when using Scribble as a
     34 documentation system for producing manuals.  In this case, the manual
     35 text is likely to start with
     36 
     37 @racketmod[scribble/doc]
     38 
     39 which installs the @"@" reader starting in ``text mode,'' wraps the
     40 file content afterward into a Racket module where many useful Racket
     41 and documentation related functions are available, and parses the body
     42 into a document using @racketmodname[scribble/decode].  See
     43 @secref["docreader"] for more information.
     44 
     45 Another way to use the reader is to use the @racket[use-at-readtable]
     46 function to switch the current readtable to a readtable that parses
     47 @tech{@"@"-forms}.  You can do this in a single command line:
     48 
     49 @commandline{racket -ile scribble/reader "(use-at-readtable)"}
     50 
     51 @;--------------------------------------------------------------------
     52 @section{Syntax Properties}
     53 
     54 The Scribble reader attaches properties to syntax objects.  These
     55 properties might be useful in some rare situations.
     56 
     57 Forms that Scribble reads are marked with a @racket['scribble]
     58 property, and a value of a list of three elements: the first is
     59 @racket['form], the second is the number of items that were read from
     60 the datum part, and the third is the number of items in the body part
     61 (strings, sub-forms, and escapes).  In both cases, a @racket[0] means
     62 an empty datum/body part, and @racket[#f] means that the corresponding
     63 part was omitted.  If the form has neither parts, the property is not
     64 attached to the result.  This property can be used to give different
     65 meanings to expressions from the datum and the body parts, for
     66 example, implicitly quoted keywords:
     67 
     68 @; FIXME: a bit of code duplication here
     69 @def+int[
     70   #:eval read-eval
     71   (define-syntax (foo stx)
     72     (let ([p (syntax-property stx 'scribble)])
     73       (printf ">>> ~s\n" (syntax->datum stx))
     74       (syntax-case stx ()
     75         [(_ x ...)
     76          (and (pair? p) (eq? (car p) 'form) (even? (cadr p)))
     77          (let loop ([n (/ (cadr p) 2)]
     78                     [as '()]
     79                     [xs (syntax->list #'(x ...))])
     80            (if (zero? n)
     81              (with-syntax ([attrs (reverse as)]
     82                            [(x ...) xs])
     83                #'(list 'foo `attrs x ...))
     84              (loop (sub1 n)
     85                    (cons (with-syntax ([key (car xs)]
     86                                        [val (cadr xs)])
     87                            #'(key ,val))
     88                          as)
     89                    (cddr xs))))])))
     90   (eval:alts
     91    (code:line
     92     @#,tt["@foo[x 1 y (* 2 3)]{blah}"])
     93     ;; Unfortunately, expressions are preserved by `def+int'
     94     ;; using `quote', not `quote-syntax' (which would create all sorts
     95     ;; or binding trouble), so we manually re-attach the property:
     96     (eval (syntax-property #'@foo[x 1 y (* 2 3)]{blah}
     97                            'scribble '(form 4 1))))
     98 ]
     99 
    100 In addition, the Scribble parser uses syntax properties to mark syntax
    101 items that are not physically in the original source --- indentation
    102 spaces and newlines.  Both of these will have a @racket['scribble]
    103 property; an indentation string of spaces will have
    104 @racket['indentation] as the value of the property, and a newline will
    105 have a @racket['(newline S)] value where @racket[S] is the original
    106 newline string including spaces that precede and follow it (which
    107 includes the indentation for the following item).  This can be used to
    108 implement a verbatim environment: drop indentation strings, and use
    109 the original source strings instead of the single-newline string.  Here
    110 is an example of this.
    111 
    112 @; FIXME: a bit of code duplication here
    113 @def+int[
    114   #:eval read-eval
    115   (define-syntax (verb stx)
    116     (syntax-case stx ()
    117       [(_ cmd item ...)
    118        #`(cmd
    119           #,@(let loop ([items (syntax->list #'(item ...))])
    120                (if (null? items)
    121                  '()
    122                  (let* ([fst  (car items)]
    123                         [prop (syntax-property fst 'scribble)]
    124                         [rst  (loop (cdr items))])
    125                    (cond [(eq? prop 'indentation) rst]
    126                          [(not (and (pair? prop)
    127                                     (eq? (car prop) 'newline)))
    128                           (cons fst rst)]
    129                          [else (cons (datum->syntax-object
    130                                       fst (cadr prop) fst)
    131                                      rst)])))))]))
    132   (eval:alts
    133    (code:line
    134     @#,tt["@verb[string-append]{"]
    135     @#,tt["  foo"]
    136     @#,tt["    bar"]
    137     @#,tt["}"])
    138    @verb[string-append]{
    139      foo
    140        bar
    141    })
    142 ]
    143 
    144 @;--------------------------------------------------------------------
    145 @section[#:tag "at-exp-lang"]{Adding @"@"-expressions to a Language}
    146 
    147 @defmodulelang[at-exp]{The @racketmodname[at-exp] language installs
    148 @seclink["reader"]{@"@"-reader} support in the readtable used to read 
    149 a module, and then chains to the reader of
    150 another language that is specified immediately after
    151 @racketmodname[at-exp].}
    152 
    153 For example, @racket[@#,hash-lang[] at-exp racket/base] adds @"@"-reader
    154 support to @racket[racket/base], so that
    155 
    156 @racketmod[
    157 at-exp racket/base
    158 
    159 (define (greet who) @#,elem{@tt["@"]@racket[string-append]@racketparenfont["{"]@racketvalfont{Hello, }@tt["@|"]@racket[who]@tt["|"]@racketvalfont{.}@racketparenfont["}"]})
    160 (greet "friend")]
    161 
    162 reports @racket["Hello, friend."].
    163 
    164 In addition to configuring the reader for a module body,
    165 @racketmodname[at-exp] attaches a run-time configuration annotation to
    166 the module, so that if it used as the main module, the
    167 @racket[current-read-interaction] parameter is adjusted to use the
    168 @seclink["reader"]{@"@"-reader} readtable extension.
    169 
    170 @history[#:changed "1.2" @elem{Added @racket[current-read-interaction]
    171                                run-time configuration.}]
    172 
    173 @;--------------------------------------------------------------------
    174 @section{Interface}
    175 
    176 @defmodule[scribble/reader]{The @racketmodname[scribble/reader] module
    177 provides direct Scribble reader functionality for advanced needs.}
    178 
    179 @; The `with-scribble-read' trick below shadows `read' and
    180 @;  `read-syntax' with for-label bindings from the Scribble reader
    181 
    182 @(define-syntax with-scribble-read
    183    (syntax-rules ()
    184      [(_)
    185       (...
    186        (begin
    187          (require (for-label scribble/reader))
    188 
    189 @; *** Start reader-import section ***
    190 @deftogether[(
    191 @defproc[(read [in input-port? (current-input-port)]) any]{}
    192 @defproc[(read-syntax [source-name any/c (object-name in)]
    193                       [in input-port? (current-input-port)])
    194          (or/c syntax? eof-object?)]
    195 )]{
    196 
    197 Implements the Scribble reader using the readtable produced by
    198 
    199 @racketblock[(make-at-readtable #:command-readtable 'dynamic
    200                                 #:datum-readtable 'dynamic)]
    201 
    202 @history[#:changed "1.1" @elem{Changed to use @racket['dynamic] for the command and datum readtables.}]}
    203 
    204 
    205 @deftogether[(
    206 @defproc[(read-inside [in input-port? (current-input-port)]) any]{}
    207 @defproc[(read-syntax-inside [source-name any/c (object-name in)]
    208                              [in input-port? (current-input-port)]
    209                              [#:command-char command-char char? #\@])
    210          (or/c syntax? eof-object?)]
    211 )]{
    212 
    213 Like @racket[read] and @racket[read-syntax], but starting as if
    214 inside a @litchar["@{"]...@litchar["}"] to return a (syntactic) list,
    215 which is useful for implementing languages that are textual by default.
    216 
    217 The given @racket[command-char] is used to customize the readtable
    218 used by the reader, effectively passing it along to @racket[make-at-readtable].
    219 
    220 @history[#:changed "1.1" @elem{Changed to use @racket['dynamic] for the command and datum readtables.}]
    221 }
    222 
    223 @defproc[(make-at-readtable
    224           [#:readtable readtable readtable? (current-readtable)]
    225           [#:command-char command-char char? #\@]
    226           [#:command-readtable command-readtable (or/c readtable? 'dynamic) readtable]
    227           [#:datum-readtable datum-readtable
    228                              (or/c readtable?
    229                                    boolean?
    230                                    (readtable? . -> . readtable?)
    231                                    'dynamic)
    232                              #t]
    233           [#:syntax-post-processor syntax-post-proc
    234                                    (syntax? . -> . syntax?)
    235                                    values])
    236           readtable?]{
    237 
    238 Constructs an @"@"-readtable.  The keyword arguments can customize the
    239 resulting reader in several ways:
    240 
    241 @itemize[
    242 
    243 @item{@racket[readtable] --- a readtable to base the @"@"-readtable
    244   on.}
    245 
    246 @item{@racket[command-char] --- the character used for @tech{@"@"-forms}.}
    247 
    248 @item{@racket[command-readtable] --- determines the readtable that is
    249   extended for reading the command part of an @tech{@"@"-form}:
    250 
    251   @itemlist[
    252     @item{a readtable --- extended to make @litchar{|} a delimiter
    253           instead of a symbol-quoting character}
    254 
    255     @item{@racket['dynamic] --- extends @racket[(current-readtable)]
    256           at the point where a command is parsed to make @litchar{|} a
    257           delimiter}
    258    ]}
    259 
    260 @item{@racket[datum-readtable] --- the readtable used for
    261   reading the datum part of an @tech{@"@"-form}:
    262 
    263   @itemlist[
    264     @item{@racket[#t] --- uses the constructed @"@"-readtable itself}
    265     @item{a readtable --- uses the given readtable}
    266     @item{a readtable-to-readtable function --- called to construct a readtable
    267           from the generated @"@"-readtable}
    268     @item{@racket['dynamic] --- uses @racket[(current-readtable)] at the
    269           point where the datum part is parsed}
    270   ]
    271 
    272   The idea is that you may want to have completely
    273   different uses for the datum part, for example, introducing a
    274   convenient @litchar{key=val} syntax for attributes.}
    275 
    276 @item{@racket[syntax-post-proc] --- function that is applied on
    277   each resulting syntax value after it has been parsed (but before it
    278   is wrapped quoting punctuations).  You can use this to further
    279   control uses of @tech{@"@"-forms}, for example, making the command be the
    280   head of a list:
    281 
    282   @racketblock[
    283     (use-at-readtable
    284       #:syntax-post-processor
    285       (lambda (stx)
    286         (syntax-case stx ()
    287           [(cmd rest ...) #'(list 'cmd rest ...)]
    288           [_else (error "@ forms must have a body")])))
    289   ]}
    290 
    291 ]
    292 
    293 @history[#:changed "1.1" @elem{Added @racket[#:command-readtable] and
    294          the @racket['dynamic] option for @racket[#:datum-readtable].}]}
    295 
    296 
    297 @defproc[(make-at-reader [#:syntax? syntax? #t] [#:inside? inside? #f] ...)
    298           procedure?]{
    299 Constructs a variant of a @"@"-readtable.  The arguments are the same
    300 as in @racket[make-at-readtable], with two more that determine the
    301 kind of reader function that will be created: @racket[syntax?] chooses
    302 between a @racket[read]- or @racket[read-syntax]-like function, and
    303 @racket[inside?] chooses a plain reader or an @racketid[-inside]
    304 variant.
    305 
    306 The resulting function has a different contract and action based on
    307 these inputs.  The expected inputs are as in @racket[read] or
    308 @racket[read-syntax] depending on @racket[syntax?]; the function will
    309 read a single expression or, if @racket[inside?] is true, the whole
    310 input; it will return a syntactic list of expressions rather than a
    311 single one in this case.
    312 
    313 Note that @racket[syntax?] defaults to @racket[#t], as this is the
    314 more expected common case when you're dealing with concrete-syntax
    315 reading.
    316 
    317 Note that if @racket[syntax?] is true, the @racket[read]-like function
    318 is constructed by simply converting a syntax result back into a datum.}
    319 
    320 
    321 @defproc[(use-at-readtable ...) void?]{
    322 
    323 Passes all arguments to @racket[make-at-readtable], and installs the
    324 resulting readtable using @racket[current-readtable]. It also enables
    325 line counting for the current input-port via @racket[port-count-lines!].
    326 
    327 This is mostly useful for playing with the Scribble syntax on the REPL.}
    328 
    329 @; *** End reader-import section ***
    330 ))]))
    331 @with-scribble-read[]
    332 
    333 @; --------------------------------------------------
    334 @(close-eval read-eval)
    335