How do I jump out of a function in Lisp? - return

Is it possible in (Common) Lisp to jump to another function instead of call another?
I mean, that the current function is broken and another is called, without jumping back through thousands of functions, as if I'd decide myself if tail call optimization is done, even if it is not the tail.
I'm not sure if "(return-from fn x)" does, what I want.
Example:
(defun fn (x)
(when x
(princ x)
(jump 'fn (cdr x)))
(rest))
'jump' should be like calling the following function without saving the position of this function, instead returning to, where the original funcall was, so that there will be no stack overflow.
'rest' should only be executed if x is nil.

When you need a tail call optimization like structure in a language that doesn't (necessarily) provide it, but does provide closures, you can use a trampoline to achieve constant stack space (with a trade off for heap space for closure objects, of course). This isn't quite the same as what you asking for, but you might find it useful. It's pretty easy to implement in Common Lisp:
(defstruct thunk closure)
(defmacro thunk (&body body)
`(make-thunk :closure (lambda () ,#body)))
(defun trampoline (thunk)
(do ((thunk thunk (funcall (thunk-closure thunk))))
((not (thunk-p thunk)) thunk)))
To use the trampoline, you just call it with a thunk that performs the first part of your computation. That closure can either return another thunk, or a result. If it returns a thunk, then since it returned the initial stack frame is reclaimed, and then the closure of returned thunk is invoked. For instance, here's what an implementation of non-variadic mapcar might look like:
(defun t-mapcar1 (function list)
(labels ((m (list acc)
(if (endp list)
(nreverse acc)
(thunk
(m (rest list)
(list* (funcall function (first list)) acc))))))
(m list '())))
When the list is empty, we get an empty list immediately:
CL-USER> (t-mapcar1 '1+ '())
NIL
When it's not, we get back a thunk:
CL-USER> (t-mapcar1 '1+ '(1 2))
#S(THUNK :CLOSURE #<CLOSURE (LAMBDA #) {10033C7B39}>)
This means that we should wrap a call with trampoline (and this works fine for the base case too, since trampoline passes non-thunk values through):
CL-USER> (trampoline (t-mapcar1 '1+ '()))
NIL
CL-USER> (trampoline (t-mapcar1 '1+ '(1 2)))
(2 3)
CL-USER> (trampoline (t-mapcar1 '1+ '(1 2 3 4)))
(2 3 4 5)
Your example code isn't quite enough to be an illustrative example, but
(defun fn (x)
(when x
(princ x)
(jump 'fn (cdr x)))
(rest))
would become the following. The return provides the early termination from fn, and the thunk value that's returned provides the “next” computation that the trampoline would invoke for you.
(defun fn (x)
(when x
(princ x)
(return (thunk (fn (cdr x)))))
(rest))

How about you use a tail call?
(defun fn (x)
(if x
(progn
(princ x)
(fn (cdr x)))
(progn
(rest))))
It calls fn in a tail position. If an implementation provides tail call optimization, you won't get a stack overflow. If you don't want to rely on that, you would need to handle the problem in a non recursive way. There are no explicit 'remove this functions stack frame and then call function X' operators in Common Lisp.

Well, not really. I once did experiment with
(defmacro recurr (name bindings &body body)
(let* ((names (mapcar #'car bindings))
(restart (gensym "RESTART-"))
(temp1 (gensym))
(temp2 (gensym))
(shadows (mapcar (lambda (name) (declare (ignore name)) (gensym)) names)))
`(block ,name
(let ,bindings
(macrolet ((,name ,shadows
(list 'progn
(cons 'psetq
(loop
:for ,temp1 :in ',names
:for ,temp2 :in (list ,#shadows)
:nconcing (list ,temp1 ,temp2)))
(list 'go ',restart))))
(tagbody
,restart
(progn ,#body)))))))
and to be used like scheme's named-let, e.g.:
(recurr traverse ((list '(1 2 3 4)))
(if (null list) 'end
(traverse (cdr list))))
but:
The object defined (traverse in the example) is not a function, i.e., you cannot funcall or apply it
This kind of construct doesn't really cope with recursive structures (i.e., since no stack is kept, you cannot use it to traverse over arbitrary trees instead of sequences)
Another approach might be
(defmacro label (name (&rest bindings) &body body)
`(labels ((,name ,(mapcar #'first bindings) ,#body))
(,name ,#(mapcar #'second bindings))))
which actually addresses the points mentioned, but loses the "look ma, no stack space consing" property.

Related

Delayed "let" in SICP

SICP indicates cdr is opened up:
In section 3.5.4 , i saw this block:
(define (integral delayed-integrand initial-value dt)
(define int
(cons-stream initial-value
(let ((integrand (force delayed-integrand)))
(add-streams (scale-stream integrand dt)
int))))
int)
Normally if this was something like:
(define (stream-map proc s)
(if (stream-null? s)
the-empty-stream
(cons-stream (proc (stream-car s))
(stream-map proc (stream-cdr s)))))
The stream-cdr s would be evaluated as (cons-stream (stream-car (cdr s)) delay<>) even when the actual call would be in a delay. ie even though the stream-map function itself is delayed, the arguments are pre-computed. [Is this correct? - By the applicative model, the arguments should be substituted for ,before the function is "called", but is the call evaluation when delay is forced or when it's just specified]
Then why is let not pre-computed?
What i think? I think let is a lambda function with the variable as the arguments, so it's execution is delayed
(let ((var1 e1) (var2 e2)) e3)
is same as
Lambda (var1 var2) e3 (with var1 bound to e1 and var2 bound to e2)
Can someone please help me confirm this? Thanks
In SICP type streams the car of a stream is not delayed, but the cdr is.
The whole expression,
(let ((integrand (force delayed-integrand)))
(add-streams (scale-stream integrand dt)
int))
, is delayed since it is the second argument to cons-stream. What kind of expression is delayed doesn't matter so you can have a call, evaluation of variable or even a let there.
"the arguments are pre-computed. is this correct?"
No. (cons-stream a (func (stream-cdr b))) is just like
(cons-stream a
(lambda ()
;; our code is placed here, verbatim, as a whole:
(func (stream-cdr b))
)
)
const-stream is a macro, it just moves pieces of code around.
The lambda might be enclosed in a memo-proc call for the memoization, to do call-by-need, but it'll still have the code we wrote, like (func (stream-cdr b)), placed inside the lambda, "textually", by cons-stream. Which is a macro, just moving pieces of code around.
Regarding the snippet which you've added to the question, the authors were just being imprecise. What is meant there is, when (stream-cdr stream) in (stream-filter pred (stream-cdr stream)) will be called, it will produce (cons 10008 (delay .... )), as shown. Not before.
Where it says "which in this case is" is should have said "which in this case is the same as".
In section 3.5.1 Streams Are Delayed Lists the book says:
To make the stream implementation automatically and transparently interleave the construction of a stream with its use, we will arrange for the cdr of a stream to be evaluated when it is accessed by the stream-cdr procedure rather than when the stream is constructed by cons-stream.

Scheme: problem about display when using `delay` expression

This is a problem related to ex3.51 in SICP, here is the code
(define (cons-stream x y)
(cons x (delay y)))
(define (stream-car stream) (car stream))
(define (stream-cdr stream) (force (cdr stream)))
(define (stream-map proc s)
(if (stream-null? s)
the-empty-stream
(cons-stream
(proc (stream-car s))
(stream-map proc (stream-cdr s)))))
(define (stream-enumerate-interval low high)
(if (> low high)
the-empty-stream
(cons-stream
low
(stream-enumerate-interval (+ low 1) high))))
(define (stream-ref s n)
(if (= n 0)
(stream-car s)
(stream-ref (stream-cdr s) (- n 1))))
(define (show x)
(display x)
x)
;test
(stream-map show (stream-enumerate-interval 0 10))
the output is 012345678910(0 . #<promise>).
but I thought the delay expression in cons-stream delayed the evaluation, if i use a different processing function in stream-map like lambda (x) (+ x 1) the output (1 . #<promise>) is more reasonable, so why does display print all the numbers?
The problem is with this definition:
(define (cons-stream x y)
(cons x (delay y)))
It defines cons-stream as a function, since it uses define.
Scheme's evaluation is eager: the arguments are evaluated before the function body is entered. Thus y is already fully calculated when it is passed to delay.
Instead, cons-stream should be defined as a macro, like
(define-syntax cons-stream
(syntax-rules ()
((_ a b) (cons a (delay b)))))
or we can call delay explicitly, manually, like e.g.
(define (stream-map proc s)
(if (stream-null? s)
the-empty-stream
(cons
(proc (stream-car s))
(delay
(stream-map proc (stream-cdr s))))))
Then there'd be no calls to cons-stream in our code, only the (cons A (delay B)) calls. And delay is a macro (or special form, whatever), it does not evaluate its arguments before working but rather goes straight to manipulating the argument expressions instead.
And we could even drop the calls to delay, and replace (cons A (delay B)) with (cons A (lambda () B)). This would entail also reimplementing force (which is built-in, and goes together with the built-in delay) as simply (define (force x) (x)) or just calling the (x) manually where appropriate to force a stream's tail.
You can see such lambda-based streams code towards the end of this answer, or an ideone entry (for this RosettaCode entry) without any macros using the explicit lambdas instead. This approach can change the performance of the code though, as delay is memoizing but lambda-based streams are not. The difference will be seen if we ever try to access a stream's element more than once.
See also this answer for yet another take on streams implementation, surgically modifying list's last cons cell as a memoizing force.

Defining a closure in terms of another closure

I have two closures that are complement of each other. I want to define one in terms of the other one. For example, lets say that we have the function more-than defined as follows
(defun more-than (v) #'(lambda (x) (> x v)))
CL-USER> (funcall (more-than 5) 7)
T
CL-USER> (funcall (more-than 5) 3)
NIL
and we want to define its complement, less-than-or-equal using the above closure. This seems to be not as easy as the above closure, as my attempts have not worked so far. Can somebody point out at a possible solution or tell me if this is common pattern at all (i.e., instead of defining the second closure independent of the first one).
Here are two of my tries that didn't work
;; compile time error
(defun less-than-or-equal (v)
#'(lambda (x) #'(not (more-than v))))
;; returns nil for every comparison
(defun less-than-or-equal (v)
#'(lambda (x) (not (more-than v))))
As I mentioned in the comments, you can use COMPLEMENT to make the complement of a function:
(defun less-than-or-equal (v)
(complement (more-than v)))
In your attempts you're using NOT to negate the function returned by MORE-THAN, rather than calling the function and negating the result. X is not used at all. To fix it, you would need to do
(defun less-than-or-equal (v)
;; The #' is not necessary here
(lambda (x) (not (funcall (more-than v) x))))
But using COMPLEMENT is better.

Streams and the substitution model

I am wondering how the substitution model can be used to show certain things about infinite streams. For example, say you have a stream that puts n in the nth spot and so on inductively. I define it below:
(define all-ints
(lambda ((n <integer>))
(stream-cons n (all-ints (+ 1 n)))))
(define integers (all-ints 1))
It is pretty clear that this does what it is supposed to, but how would someone go about proving it? I decided to use induction. Specifically, induction on k where
(last (stream-to-list integers k))
provides the last value of the first k values of the stream provided, in this case integers. I define stream-to-list below:
(define stream-to-list
(lambda ((s <stream>) (n <integer>))
(cond ((or (zero? n) (stream-empty? s)) '())
(else (cons (stream-first s)
(stream-to-list (stream-rest s) (- n 1)))))))
What I'd like to prove, specifically, is the property that k = (last (stream-to-list integers k)) for all k > 1.
Getting the base case is fairly easy and I can do that, but how would I go about showing the "inductive case" as thoroughly as possible? Since computing the item in the k+1th spot requires that the previous k items also be computed, I don't know how this could be shown. Could someone give me some hints?
In particular, if someone could explain how, exactly, streams are interpreted using the substitution model, I'd really appreciate it. I know they have to be different from the other constructs a regular student would have learned before streams, because they delay computation and I feel like that means they can't be evaluated completely. In turn this would man, I think, the substitution model's apply eval apply etc pattern would not be followed.
stream-cons is a special form. It equalent to wrapping both arguments in lambdas, making them thunks. like this:
(stream-cons n (all-ints (+ 1 n))) ; ==>
(cons (lambda () n) (lambda () (all-ints (+ n 1))))
These procedures are made with the lexical scopes so here n is the initial value while when forcing the tail would call all-ints again in a new lexical scope giving a new n that is then captured in the the next stream-cons. The procedures steam-first and stream-rest are something like this:
(define (stream-first s)
(if (null? (car s))
'()
((car s))))
(define (stream-rest s)
(if (null? (cdr s))
'()
((cdr s))))
Now all of this are half truths. The fact is they are not functional since they mutates (memoize) the value so the same value is not computed twice, but this is not a problem for the substitution model since side effects are off limits anyway. To get a feel for how it's really done see the SICP wizards in action. Notice that the original streams only delayed the tail while modern stream libraries delay both head and tail.

Compose example in Paul Graham's ANSI Common Lisp

Can anybody explain an example in Paul Graham's ANSI Common Lisp page 110?
The example try to explain the use &rest and lambda to create functional programming facilities. One of them is a function to compose functional arguments. I cannot find anything explaining how it worked. The code is as follows:
(defun compose (&rest fns)
(destructuring-bind (fn1 . rest) (reverse fns)
#'(lambda (&rest args)
(reduce #'(lambda (v f) (funcall f v))
rest
:initial-value (apply fn1 args)))))
The usage is:
(mapcar (compose #'list #'round #'sqrt)
'(4 9 16 25))
The output is:
((2) (3) (4) (5))
Line 2 and 6 look especially like magic to me.
The compose function returns a closure that calls each of the functions from last to first, passing on the result of each function call to the next.
The closure resulting from calling (compose #'list #'round #'sqrt) first calculates the square root of its argument, rounds the result to the nearest integer, then creates a list of the result. Calling the closure with say 3 as argument is equivalent to evaluating (list (round (sqrt 3))).
The destructuring-bind evaluates the (reverse fns) expression to get the arguments of compose in reverse order, and binds its first item of the resulting list to the fn1 local variable and the rest of the resulting list to the rest local variable. Hence fn1 holds the last item of fns, #'sqrt.
The reduce calls each the fns functions with the accumulated result. The :initial-value (apply fn1 args) provides the initial value to the reduce function and supports calling the closure with multiple arguments. Without the requirement of multiple arguments, compose can be simplified to:
(defun compose (&rest fns)
#'(lambda (arg)
(reduce #'(lambda (v f) (funcall f v))
(reverse fns)
:initial-value arg)))
destructuring-bind combines destructors with binding. A destructor is a function that lets you access a part of a data structure. car and cdr are simple destructors to extract the head and tail of a list. getf is a general destructor framework. Binding is most commonly performed by let. In this example, fns is (#'list #'round #'sqrt) (the arguments to compose), so (reverse fns) is (#'sqrt #'round #'list). Then
(destructuring-bind (fn1 . rest) '(#'sqrt #'round #'list)
...)
is equivalent to
(let ((tmp '(#'sqrt #'round #'list)))
(let ((fn1 (car tmp))
(rest (cdr tmp)))
...))
except that it doesn't bind tmp, of course. The idea of destructuring-bind is that it's a pattern matching construct: its first argument is a pattern that the data must match, and symbols in the pattern are bound to the corresponding pieces of the data.
So now fn1 is #'sqrt and rest is (#'round #'list). The compose function returns a function: (lambda (&rest args) ...). Now consider what happens when you apply that function to some argument such as 4. The lambda can be applied, yielding
(reduce #'(lambda (v f) (funcall f v))
'(#'round #'list)
:initial-value (apply #'sqrt 4)))
The apply function applies fn1 to the argument; since this argument is not a list, this is just (#'sqrt 4) which is 2. In other words, we have
(reduce #'(lambda (v f) (funcall f v))
'(#'round #'list)
:initial-value 2)
Now the reduce function does its job, which is to apply #'(lambda (v f) (funcall f v)) successively to the #'round and to #'list, starting with 2. This is equivalent to
(funcall #'list (funcall #'round 2))
→ (#'list (#'round 2))
→ '(2)
Okay, here goes:
It takes the functions given, reverses it (in your example, it becomes (#'sqrt #'round #'list)), then sticks the first item into fn1, and the rest into rest. We have: fn1 = #'sqrt, and rest = (#'round #'list).
Then it performs a fold, using (apply sqrt args) (where args are the values given to the resulting lambda) as the initial value, and with each iteration grabbing the next function from rest to call.
For the first iteration you end up with (round (apply sqrt args)), and the second iteration you end up with (list (round (apply sqrt args))).
Interestingly, only the initial function (sqrt in your case) is allowed to take multiple arguments. The rest of the functions are called with single arguments only, even if any particular function in the chain does a multiple-value return.
This example stumped me for a day. I could finally understand it by renaming some of the arguments and commenting each line before it made sense. Below is what helped me explain it to myself.
In the book example using the call:
(mapcar (compose #'list #'round #'sqrt) '(4 9 16 25))
The parameter functions becomes (#'LIST #'ROUND #'SQRT)
(defun compose (&rest functions)
(destructuring-bind (fx . fxs) (reverse functions)
;; fx becomes #'SQRT
;; fxs becomes '(#'ROUND #'LIST)
#'(lambda (&rest args) ; This is the function returned as result.
;; The args parameter will be (4) on the mapcar's first
;; iteration on the (4 9 16 25) list passed in the call:
;; (mapcar #'(compose #'List #'round #'sqrt) '(4 9 16 25)) => ((2) (3) (4) (5))
;; or e.g. the (4) in (funcall (compose #'list #'sqrt '(4)) => (2.0)
;; Note that args is not ((#'ROUND #'LIST)).
(reduce #'(lambda (x y) (funcall y x))
;; fxs is (#'ROUND #'LIST) - captuted as closure since it is now
;; locally unbound.
fxs
;; Initial value is: (apply #'SQRT '(4) => 2.0.
;; In Paul Graham's example, the mapcar passes
;; each square number individually.
;; The reverse order of parameters in the second lambda
;; first invokes: (ROUND 2.0) => 2
;; and then invokes: (LIST 2) => (2)
:initial-value (apply fx args)))))

Resources