How to map a macro over a list - or - How to use macros to define data types - macros

I like to build a REPL with my own datatypes, but I don't like to write all the same pattern functions over and over again.
So this is a nut, which bothers me.
I got my own set of primitive datatypes (define primitives '("mytrue" "myfalse" "mynumber" ...))
Also I have (define primitiveTesters (list "mytrue?" "myfalse?" "mynumber?" ... )
The problem now is, I just want to apply (map) or a macro to get the datatype? procedurces, which basically just checks if the car of record (mynumber . ( . )) exists.
So something similar like (mynumber? (car (mynumber.(1.))) => #t in the end. But for this I need (define mynumber? (lambda (...)(...))
My define-batching macro looks like this, but I just have no luck to infuse the <variable>.
(define-syntax define-batching
(syntax-rules ()
((_ value expr)(define value expr))
((_ value) value)
((_ value1 value2 ...) (begin (define value1 expr) (define-batching test2...)))
))
So have I reached a dead end of scheme ?
I've seen something similar, I think in Emacs Lisp.
What I am looking for in the end is:
(define checker '(audi? volkswagen? mercedes?))
(define datatype '(audi volkswagen mercedes))
(map define-checker checker datatype )
or
(define-checker (car checker) (car datatype))

If I understood the question right, you need a macro
to define your own type checkers?
Here is one way to do it:
(define-syntax define-checker
(syntax-rules ()
[(define-checker name tag)
(define (name object)
(and (list? object)
(not (null? object))
(eq? (car object) 'tag)))]))
(define-checker my-car? car)
(my-car? '(car audi black)) ; evaluates to #t
(my-car? '(truck ford pink)) ; evaluates to #f
Addendum:
If you write
(define checker '(audi? volkswagen? mercedes?))
(define datatype '(audi volkswagen mercedes))
the values will become available at runtime.
Therefore you need to a different approach.
You could for example write:
(define-checker+datatype (audi? audi) (volkswagen? volkswagen?))
Here is the code:
(define-syntax define-checker
(syntax-rules ()
[(define-checker name tag)
(define (name object)
(and (list? object)
(not (null? object))
(eq? (car object) 'tag)))]))
(define-syntax define-checkers+datatype
(syntax-rules ()
[(define-checkers+datatype (name tag) ...)
(begin
(define-checker name tag)
...)]))
(define-checkers+datatype (audi? audi) (wv? wv))
(audi? '(audi black))

define-syntax is hygienic, that means it cannot influence on parent environment, that means it cannot define symbols in it.
You may try to use er-, ir- macro-transformers which allow you to explicit renames symbols.
keywords to google in you scheme documentation are 'er-macro-transformet' and 'ir-macro-transformer'

Related

Creating equivalent to incf as macro-function in lisp

I'm just starting to learn the concept of macro functions.
My teacher has asked us to create a macro function that would function exactly the same way as incf.
Here is an example he has given us for pop
(defmacro mypop (nom)
(list 'prog1 (list 'car nom) (list 'setq nom (list 'cdr nom))) )
Here is the regular function I'm trying to turn into a macro:
(defun iincf (elem &optional num )
(cond
((not num) (setq elem (+ 1 elem)))
(t (setq elem (+ num elem))) ) )
Here is my attempt at turning it into a macro :
(defmacro myincf (elem &optional num )
(list 'cond
((list 'not num) (list 'setq elem (list '+ 1 elem)))
(t (list 'setq elem (list '+ num elem))) ) )
However, I get this error and I don't know why:
*** - system::%expand-form: (list 'not num) should be a lambda expression
Also, I'm not sure whether my function would actually change the value of the variable at the top level.
So here are my 2 questions:
Why do I get this error?
Is the function I'm trying to turn into a macro fine? (if successfully turning it into a macro function, would it do what I intend to?)
PS: I know this exercise would probably infringe many common rules in lisp, but this is just for practice. Thanks! :)
The reason for the error is that your syntax is invalid:
((list ...) ...)
(t (list ...))
The first element should be a function name or a lambda expression, so you would need to change it to something like
(list (list ...) ...)
(list t (list ...))
Although the macro isn't a very good one yet. First of all, the backquote syntax would make the code much more readable. It allows you to write a template where only the specified forms are evaluated. For example, the given MYPOP macro would look like
(defmacro mypop (nom)
`(prog1 (car ,nom)
(setq ,nom (cdr ,nom))))
Only the forms with a comma before them are evaluated. Same with your macro:
(defmacro myincf (elem &optional num)
`(cond
((not ,num) (setq ,elem (+ 1 ,elem)))
(t (setq ,elem (+ ,num ,elem)))))
The COND shouldn't really be part of the expansion though. It should be evaluated during macroexpansion, and only the SETQ form from one of the branches returned.
(defmacro myincf (elem &optional num)
(cond
((not num) `(setq ,elem (+ 1 ,elem)))
(t `(setq ,elem (+ ,num ,elem)))))
The only difference between the two branches is that the first one defaults to 1 for NUM. A simpler way to achieve the same would be to give NUM a default value.
(defmacro myincf (elem &optional (num 1))
`(setq ,elem (+ ,num ,elem)))
Of course, the standard INCF is a bit more complex, since it works for all sorts of places (not just variables) and ensures that the subforms of the place are evaluated only once. However, since the MYPOP example doesn't handle those, I don't think you have to either.
If you want to, a simple way to define such a macro would be
(define-modify-macro myincf (&optional (num 1)) +)
Or you could do the same manually with something like
(defmacro myincf (place &optional (num 1) &environment env)
(multiple-value-bind (dummies vals store setter getter)
(get-setf-expansion place env)
`(let* (,#(mapcar #'list dummies vals)
(,(first store) (+ ,getter ,num)))
,setter)))
But using DEFINE-MODIFY-MACRO would be preferrable in a real program (shorter code, less bugs). You could read about GET-SETF-EXPANSION and DEFINE-MODIFY-MACRO if you're interested.

Scheme self-reference lambda macro

(define-macro slambda
(lambda (args body)
`(let ((self (lambda ,args ,body)))
self)))
Hello, I have a "problem" with this macro for self-referencing lambda.. It works, but fails when I want to refer to "self" from outside.. meaning that first aplication works, second doesn't
((slambda (x) (+ x 1)) 10)
((slambda () self))
Perhaps it would work better you replaced let for letrec like this:
(define-macro slambda
(lambda (args body)
`(letrec ((self (lambda ,args ,body)))
self)))
In Scheme you have lexical scope and self is not in effect until the body of the let. The procedure called self in the body of the let is not defined by that name inside itself. It's perhaps easier to see if you desugar let:
((lambda (self) ...)
(lambda () self)) ; self referenced outside procedure that defines it
Notice that define-macro isn't a standard scheme syntax so you should have specified which implementation you are using. Luckily this problem had nothing to do with macros.
If you are using scheme you might be better off using standard define-syntax rather than the not-always-supported define-macro. With define-syntax, you have to use datum->syntax to get the macro to act unhygienically and inject the name 'self' into the output syntax. This is your code translated to define-syntax, as tested with guile:
(define-syntax slambda
(lambda (x)
(syntax-case x ()
[(slambda formals body0 body1 ...)
(with-syntax ([self (datum->syntax #'slambda 'self)])
#'(letrec ([self (lambda formals body0 body1 ...)])
self))])))
You need to quote the lambda-part where you quasiqute so it can be assigned to self.
(define-macro slambda
(lambda (arg1 . arg2)
`(let ((self '(slambda ,arg1 ,#arg2)))
(lambda ,arg1 ,#arg2))))
The dot and unquote-splicing is needed there if you want to use it with more than one argument.
Sylwester's answer is correct, but I wanted to make a bigger point: unless your Scheme implementation doesn't provide a hygienic procedural macro system, there is no good reason to use define-macro.
For anaphoric macros, such as the one you want to write, it's best to use syntax parameters, if you're using a Scheme implementation that supports it, such as Racket or Guile. Here's a Racket example:
#lang racket
(provide slambda self)
(require racket/stxparam srfi/31)
(define-syntax-parameter self
(lambda (stx)
(raise-syntax-error 'self "Can only be used inside slambda")))
(define-syntax slambda
(syntax-rules ()
((_ params body ...)
(rec (ohai . params)
(syntax-parameterize ((self (make-rename-transformer #'ohai)))
body ...)))))
Of course, as you can see in my example, I used rec. In the general case where you want to make self-referential procedures, it's best to use rec for that; you simply specify the name you want to refer to the procedure by (rather than using a hardcoded self). Since rec is not anaphoric, its definition is much simpler:
(define-syntax rec
(syntax-rules ()
((_ (id . params) body ...)
(rec id (lambda params body ...)))
((_ id value)
(letrec ((id value)) id))))
You would use it like this (in this case, I use recur as the self-reference; of course, you can choose any name you like):
(define nested-length
(rec (recur x)
(cond ((null? x) 0)
((pair? x) (+ (recur (car x)) (recur (cdr x))))
(else 1))))

Is struct a macro in Racket?

I remember I read somewhere it is not a macro and is built into the core language. Something like that, I am not sure, because I can no longer remember from where I read it. So is struct a macro in Racket or not? If not, why is it built into the core language?
A macro; struct.rkthas
(define-syntax (struct stx)
(define (config-has-name? config)
(cond
[(syntax? config) (config-has-name? (syntax-e config))]
[(pair? config) (or (eq? (syntax-e (car config)) '#:constructor-name)
(eq? (syntax-e (car config)) '#:extra-constructor-name)
(config-has-name? (cdr config)))]
[else #f]))
(with-syntax ([orig stx])
(syntax-case stx ()
[(_ id super-id fields . config)
(and (identifier? #'id)
(identifier? #'super-id))
(if (not (config-has-name? #'config))
(syntax/loc stx
(define-struct/derived orig (id super-id) fields #:constructor-name id . config))
(syntax/loc stx
(define-struct/derived orig (id super-id) fields . config)))]
[(_ id fields . config)
(identifier? #'id)
(if (not (config-has-name? #'config))
(syntax/loc stx
(define-struct/derived orig id fields #:constructor-name id . config))
(syntax/loc stx
(define-struct/derived orig id fields . config)))]
[(_ id . rest)
(identifier? #'id)
(syntax/loc stx
(define-struct/derived orig id . rest))]
[(_ thing . _)
(raise-syntax-error #f
"expected an identifier for the structure type name"
stx
#'thing)]))))
In Racket IDE, you can use the Open Defining File function to locate the source code (if available).
It looks like I misunderstood the question, when I answered before. So here's an answer to the question that was meant:
Structs are built-in and primitive; they underpin the implementation. In fact, circa 2007, Matthew Flatt commented that in PLT Scheme (as Racket was known then), in a sense everything is a struct:
> At Thu, 31 May 2007 16:45:25 -0700, YC wrote:
> Out of curiosity - does PLT scheme actually use struct as the fundamental
> compound type, i.e. implement closure/etc on top of struct.
The way I think about it, everything is a struct, but some things use a
special-case representation because they're important enough. (The
extreme case is a fixnum).
But an equally valid answer would be: no, not all compound types use
the same representation as values from a struct constructor.
-- Source.
Start of the thread.
In addition to usepla's great answer, I wanted to add:
In the Racket documentation, the "blue box" has a phrase in the top right corner such as procedure or syntax. For struct it says syntax.
If you think about what struct does, among other things it defines named functions derived from the name of the struct. So (struct foo (a b)) will define a foo? predicate and accessors foo-a, foo-b. A plain function can't define new named things like this, so, it must be a macro.
Reading through the implementation code in define-struct.rkt, if you want to do the same thing manually, the following code is a much simplified version of what it is doing.
(define-syntax (struct stx)
;
; Function that creates compound names using syntax objects
(define (make-name id . parts)
(datum->syntax
id
(string->symbol
(apply string-append
(map (lambda (p)
(if (syntax? p)
(symbol->string (syntax-e p))
p))
parts)))
id))
;
(syntax-case stx ()
;
; parse the input and extract the name and variable
; this version uses only one variable for simplicity (3)
[(_ id avar)
;
; guard to ensure we have an identifier
(identifier? #'id)
;
; Create the names (1)
(let ((? (make-name #'id #'id "?"))
(v (make-name #'id #'id "-" #'avar)))
; Generate code to define the various functions associated with
; the new struct (2)
#`(begin
(define id (lambda (vx) (list id vx)))
(define #,? (lambda (x) (eq? (car x) id)))
(define #,v (lambda (x) (second x)))))]
))
1) We have to create the names we will define: but we need to use syntax objects to do so
2) We generate code that will define all of the functions associated with the new object in the global namespace
3) In the real version, most of the code deals with the properties that can be used a struct definition. The real version also needs to handle arbitrary numbers of variables and alternative forms, defaults etc...

set! global from Scheme macro?

I am trying to write a wrapper for define, that stores the values passed to it. I've been approaching it in baby steps (being new to Lisp in general, and even newer to Scheme) but have run into a wall.
In Racket, I'm starting with:
> (require (lib "defmacro.ss"))
> (define-macro (mydefine thing definition)
`(define ,thing ,definition))
> (mydefine a 9)
> a
9
Okay, that works. Time to do something in the macro, prior to returning the s-exprs:
> (define-macro (mydefine thing definition)
(display "This works")
`(define ,thing ,definition))
> (mydefine a "bob")
This works
> a
"bob"
Nice. But I can't for the life of me get it to set a global variable instead of displaying something:
> (define *myglobal* null)
> (define-macro (mydefine thing definition)
(set! *myglobal* "This does not")
`(define ,thing ,definition))
> (mydefine a ":-(")
set!: cannot set identifier before its definition: *myglobal*
Any suggestions on how to accomplish this would be greatly appreciated.
I suspect that I'm trying to swim against the current here, either by fiddling with globals from a macro in Scheme, or by using define-macro instead of learning the Scheme-specific syntax for macro creation.
You're running against Racket's phase separation -- which means that each phase (the runtime and the compile-time) operate in different worlds. As Vijay notes, one way to solve this is to do what you want at runtime, but that will probably not be what you need in the long run. The thing is that trying these things usually means that you will want to store some syntactic information at the compile-time level. For example, say that you want to store the names of all of your defined names, to be used in a second macro that will print them all out. You would do this as follows (I'm using sane macros here, define-macro is a legacy hack that shouldn't be used for real work, you can look these things up in the guide, and then in the reference):
#lang racket
(define-for-syntax defined-names '())
(define-syntax (mydefine stx)
(syntax-case stx ()
[(_ name value)
(identifier? #'name)
(begin (set! defined-names (cons #'name defined-names))
#'(define name value))]
;; provide the same syntactic sugar that `define' does
[(_ (name . args) . body)
#'(mydefine name (lambda args . body))]))
Note that defined-names is defined at the syntax level, which means that normal runtime code cannot refer to it. In fact, you can have it bound to a different value at the runtime level, since the two bindings are distinct. Now that that's done, you can write the macro that uses it -- even though defined-names is inaccessible at the runtime, it is a plain binding at the syntax level, so:
(define-syntax (show-definitions stx)
(syntax-case stx ()
[(_) (with-syntax ([(name ...) (reverse defined-names)])
#'(begin (printf "The global values are:\n")
(for ([sym (in-list '(name ...))]
[val (in-list (list name ...))])
(printf " ~s = ~s\n" sym val))))]))
The statement (set! *myglobal* "This does not") is executed in the transformer environment, not the normal environment. So it's not able to find *myglobal. We need to get both the expressions executed in the environment where *myglobal* is defined.
Here is one solution:
(define *defined-values* null)
(define-macro (mydefine thing definition)
`(begin
(set! *defined-values* (cons ,definition *defined-values*))
(define ,thing ,`(car *defined-values*))))
> (mydefine a 10)
> (mydefine b (+ 20 30))
> a
10
> b
50
> *defined-values*
(50 10)
> (define i 10)
> (mydefine a (begin (set! i (add1 i)) i)) ;; makes sure that `definition`
;; is not evaluated twice.
> a
11
If the Scheme implementation does not provide define-macro but has define-syntax, mydefine could be defined as:
(define-syntax mydefine
(syntax-rules ()
((_ thing definition)
(begin
(set! *defined-values* (cons definition *defined-values*))
(define thing (car *defined-values*))))))

How do I define functions using Racket macros?

I am trying to write a macro that defines a special class of data structure with associated functions.
I know this is possible; it is done multiple times in the core language itself.
As a specific example, how would I define the define-struct macro in Scheme itself. It needs to create make-struct, struct-<<field>>, etc functions.
I tried doing this using define, however, this only defines the function in the macro's lexical scope.
How can I actually define a function in a macro?
The key for an answer is datum->syntax. The basic idea is that you want to take some random data and turn it into a syntax -- in this case, turn a symbol into an identifier. An identifier is basically a symbol with some lexical information that (very roughly) indicates how it is bound. Using datum->syntax you can do exactly that: it expects an existing piece of syntax which is where it copies the binding from, and a datum (a symbol here) which is the value that is contained in the syntax wrapper.
Here's an example that demonstrates a define-struct-like tool using this:
#lang scheme
;; implements a defstruct-like macro that uses association lists
(define-syntax (defstruct-lite stx)
(syntax-case stx ()
[(defstruct-lite name field ...)
(let ([make-id
(lambda (template . ids)
(let ([str (apply format template (map syntax->datum ids))])
(datum->syntax stx (string->symbol str))))])
(with-syntax ([make-name (make-id "make-~a" #'name)]
[name? (make-id "~a?" #'name)]
[(arg ...) (generate-temporaries #'(field ...))]
[(name-field ...)
(map (lambda (f) (make-id "~a-~a" #'name f))
(syntax->list #'(field ...)))])
#'(begin
(define (make-name arg ...) (list 'name (cons 'field arg) ...))
(define (name? x) (and (pair? x) (eq? 'name (car x))))
(define (name-field x)
(and (name? x) (cdr (assq 'field (cdr x)))))
...)))]))
And here's an example of using it:
(defstruct-lite point x y)
(point-y (make-point 1 2))