[S:N]的宏在Racket的范围内

rns*_*nso 1 scheme racket

如何创建宏以使S:N或[S:N]返回以S开头并以N结尾的数字范围(步骤1).基本上,它应该能够用它来代替"范围内".我尝试创建类似于Curly bracket {}的东西来替换Racket中的'begin'但不能.

编辑:我尝试按照@soegaard的建议:

我-top.rkt:

#lang racket
(define-syntax-rule (my-top S:N)
    (range S N) )

(provide (rename-out [my-top #%top]))
Run Code Online (Sandbox Code Playgroud)

test.rkt:

#lang racket
 (require "my-top.rkt")

 (1:42)
Run Code Online (Sandbox Code Playgroud)

但它没有运行.错误是:

 #%top: use does not match pattern: (#%top S:N) in: (#%top . 1:42)
Run Code Online (Sandbox Code Playgroud)

[1:42]和1:42也行不通.

soe*_*ard 5

以下是S:N扩展到数字的(range S N)位置S和步骤的步骤N.

请注意,这S:N是一个标识符.因此,未绑定S:N是未绑定的标识符.对未绑定标识符的引用将n扩展为(#%top . n).因此1:42扩展到(#%top 1:42).

  1. 做一个宏my-top,从而(my-top S:N)扩展到(range S N).
  2. 将宏保存在文件中my-top.rkt并使用导出它(provide (rename-out [my-top #%top])).
  3. 像这样使用你的新结构:

.

 #lang racket
 (require "my-top.rkt")
 1:42
Run Code Online (Sandbox Code Playgroud)

步骤1:

#lang racket
(require syntax/parse (for-syntax racket/match syntax/parse))

(begin-for-syntax  
  ; contains-colon? : string -> boolean
  ;   does the string str contain a colon?
  (define (contains-colon? str)
    (regexp-match ".*:.*" str))

  ; split-colon-string-into-numbers : string -> (list number number)
  ;    for a string of the form N:S return a list consisting of the
  ;    numbers corresponsing to the substrings N and S
  (define (split-colon-string-into-numbers str)    
    (match (regexp-match "(.*):(.*)" str)
      [(list _ S-str N-str)
       (list (string->number S-str) (string->number N-str))]
      [_else
       (error 'split-colon-string-into-numbers
              "expected string of the number <number>:<number>")])))

; SYNTAX (my-top . id)
;   (my-top . id)  behaves the same as (#%top . id)
;   except when id has the form N:S in which case
;   (my-top . id) behaves as (range N S)
(define-syntax (my-top stx)
  (syntax-parse stx
    [(_my-top . identifier:id)     
     (define str (symbol->string (syntax-e #'identifier)))
     (cond
       [(contains-colon? str)
        (with-syntax ([(S N) (split-colon-string-into-numbers str)])
          (syntax/loc stx
            (range S N)))]
       [else
        #'(#%top . identifier)])]))

;;; Tests

(my-top . 1:5)    ; evaluates to (1 2 3 4)
(define foo 42)
(my-top . foo)    ; evaluates to 42
Run Code Online (Sandbox Code Playgroud)

  • 但是当`S:N`未定义时会发生什么? (2认同)

Ale*_*uth 5

@ soegaard的答案提供了一个#%top基于解决方案的解决方案,该解决方案在字面整数扩展S:NS并且未定义为标识符.但是,也可以使用阅读器宏来完成此操作.NS:N

我有两个版本:一个只适用于文字整数的简单版本,另一个适用于任意表达式的版本,包括变量.

文字整数版本

这个简单版本覆盖[了开始范围表达式,例如[S:N],where SN是字面整数.之后[,它会读取数字字符直到找到a :,然后它会读取更多的数字字符,直到找到它为止].它将数字字符串转换为整数,并将这些整数放入表示对range函数的调用的列表中.

它会像这样使用:

#lang colon-range
;; simple range by itself
[1:42]
;; using a range within a more complicated expression
(for/list ((i [2:42])
           #:when
           (for/and ((j [2:41]) #:when (< j i))
             (not (= 0 (remainder i j)))))
  i)
Run Code Online (Sandbox Code Playgroud)

请注意,我用((i ....))的,而不是更常见的([i ....]),因为我不能使用[]正常了.

要实现该#lang colon-range语言,您应该将reader实现放在colon-range/lang/reader.rkt哪里colon-range,作为单一集合包安装.

;; s-exp syntax/module-reader is a language for defining new languages.
#lang s-exp syntax/module-reader
racket
#:wrapper1 (lambda (th)
             (parameterize ([current-readtable
                             (make-colon-range-readtable (current-readtable))])
               (th)))

;; This extends the orig-readtable with an entry for `[` to convert
;; `[1:42]` to `(range 1 42)`. In this simplistic implementation, they
;; have to be literal numbers, so it can't refer to a variable.
(define (make-colon-range-readtable orig-readtable)
  (make-readtable orig-readtable
    #\[ 'terminating-macro colon-range-proc))

;; This is the function that the new readtable will use when in encounters a `[`
(define (colon-range-proc char in src ln col pos)
  (define S (read-int-until #\: in src))
  (define N (read-int-until #\] in src))
  (list 'range S N))

;; This reads until it finds the given char (consuming it),
;; and returns an exact integer
(define (read-int-until char in src)
  (define str (list->string (read-numeric-chars-until char in src)))
  (define i (string->number str))
  (unless (exact-integer? i)
    (error 'read "expected an exact integer, given `~a`" str))
  i)

;; This reads until it finds the given char (consuming it), and returns a list
;; of characters. Each char it reads before that needs to be a numeric char,
;; otherwise it throws an error.
(define (read-numeric-chars-until char in src)
  (define c (read-char in))
  (cond [(eof-object? c)
         (error 'read "end-of-file: expected either a number or a `~a`, given `~a`"
                char c)]
        [(char=? char c)
         (list)]
        [(char-numeric? c)
         (cons c (read-numeric-chars-until char in src))]
        [else
         (error 'read "expected either a number or a `~a`, given `~a`"
                char c)]))
Run Code Online (Sandbox Code Playgroud)

任意表达版本

此版本会覆盖[:.它定义:为一个分隔符,使其a:b读取相同a : b,并定义[为读取宏,读取正常列表并在之后处理它.因此,它将首先[a : b]作为三个元素的列表,然后将其转换为(range a b).

它可以像这样使用:

#lang colon-range
;; simple range by itself
[1:42]
;; using a range within a more complicated expression
(for/list ([i [2:42]]
           #:when
           (for/and ([j [2:i]]) ; can refer to a variable
             (not (= 0 (remainder i j)))))
  i)
(define two 2)
(for/list ([i [two:42]] ; can refer to a variable for the start
           #:when
           (for/and ([j [two:(+ 1 (exact-floor (sqrt i)))]]) ; can use arbitrary expressions
             (not (= 0 (remainder i j)))))
  i)
Run Code Online (Sandbox Code Playgroud)

实现看起来像这样(再次colon-range/lang/reader.rkt).评论解释了它正在做的一些事情.

;; s-exp syntax/module-reader is a language for defining new languages.
#lang s-exp syntax/module-reader
racket
#:wrapper1 (lambda (th)
             (parameterize ([current-readtable
                             (make-colon-range-readtable (current-readtable))])
               (th)))

;; This extends the orig-readtable with entries for `[` and `:` to convert
;; `[S:N]` to `(range S N)`.
(define (make-colon-range-readtable orig-readtable)
  (make-readtable orig-readtable
    #\[ 'terminating-macro colon-range-proc
    #\: 'terminating-macro separator-proc))

;; This is the function that the new readtable will use when in encounters a `[`
(define (colon-range-proc char in src ln col pos)
  ;; This reads the list of things ending with the character that closes `char`
  ;; The #f means it uses the racket reader for the first step, so that `[`
  ;; uses the normal behavior, grouping expressions into a reader-level list
  (define lst (read-syntax/recursive src in char #f))
  ;; This matches on that list to determine whether it has the shape `[S : N]`
  (syntax-case lst (:)
    [[S : N]
     ;; if it is, translate it to `(range S N)`
     (list 'range #'S #'N)]
    [_
     ;; otherwise leave it alone
     lst]))

;; This doesn't read any further and simply returns an identifier containing char,
;; so that it can act like a separator
(define (separator-proc char in src ln col pos)
  (char->identifier char (list src ln col pos 1)))

(define (char->identifier char srcloc)
  (datum->syntax #f (string->symbol (string char)) srcloc))
Run Code Online (Sandbox Code Playgroud)