From: Peter Seibel
Subject: catch/throw useful for anything?
Date: 
Message-ID: <m3vfuwf5u5.fsf@javamonkey.com>
Given the flexibility of the condition system for managing
coordination of code at different levels of the call stack, I'm having
a hard time thinking of what I'd use CATCH/THROW for.

Does anyone have any favorite idioms they still use that feature
CATCH/THROW?

And if you do use CATCH/THROW, do you ever take advantage of the tag
arguments to CATCH and THROW being evaluated? I.e. how often is the
tag in either the CATCH or the THROW not a just quoted symbol?

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp

From: Kent M Pitman
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <sfwptl455wm.fsf@shell01.TheWorld.com>
Peter Seibel <·····@javamonkey.com> writes:

> Given the flexibility of the condition system for managing
> coordination of code at different levels of the call stack, I'm having
> a hard time thinking of what I'd use CATCH/THROW for.
> 
> Does anyone have any favorite idioms they still use that feature
> CATCH/THROW?

The condition system is higher overhead due to its introduction of 
introspection capabilities.  I think CATCH/THROW is used only rarely,
but usually in situations where many people these days would use a
set of mutually recursive functions using LABELS and a lexical 
RETURN[-FROM] to exit from a tree-like search.  Some people prefer to
break this out into separate top-level functions that do (a) not share a 
common lexical contour so don't qualify for RETURN-FROM and (b) don't
want to pass a continuation arg that would be able to piggy-back the
RETURN-FROM operation.

> And if you do use CATCH/THROW, do you ever take advantage of the tag
> arguments to CATCH and THROW being evaluated? I.e. how often is the
> tag in either the CATCH or the THROW not a just quoted symbol?

I often use this in HTML parsing.  I build a stack of the elements that
are being filled and allow you to throw to certain pending elements
saying  "start a new child". e.g., when you're in a UL and an LI and you
see a new LI and realize  you need to tell the UL to start a new LI.
I just use the object I'm filling as the throw tag.
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m3isqweymo.fsf@javamonkey.com>
Kent M Pitman <······@world.std.com> writes:

> Peter Seibel <·····@javamonkey.com> writes:
> 
> > Given the flexibility of the condition system for managing
> > coordination of code at different levels of the call stack, I'm having
> > a hard time thinking of what I'd use CATCH/THROW for.
> > 
> > Does anyone have any favorite idioms they still use that feature
> > CATCH/THROW?
> 
> The condition system is higher overhead due to its introduction of
> introspection capabilities.

Just out of curiosity, isn't there some (unexposed) introspection
going on with THROW too? That is, THROW has to be able to tell whether
there's a CATCHer waiting for it before it actually unwinds the stack,
right? So there must be some dynamic datastructure maintained under
the covers to support that. Or are you talking about the space
overhead of the extra information that has to be stored at runtime
associated with restarts?

> I think CATCH/THROW is used only rarely, but usually in situations
> where many people these days would use a set of mutually recursive
> functions using LABELS and a lexical RETURN[-FROM] to exit from a
> tree-like search. Some people prefer to break this out into separate
> top-level functions that do (a) not share a common lexical contour
> so don't qualify for RETURN-FROM and (b) don't want to pass a
> continuation arg that would be able to piggy-back the RETURN-FROM
> operation.

That makes sense.

> > And if you do use CATCH/THROW, do you ever take advantage of the tag
> > arguments to CATCH and THROW being evaluated? I.e. how often is the
> > tag in either the CATCH or the THROW not a just quoted symbol?
> 
> I often use this in HTML parsing.  I build a stack of the elements that
> are being filled and allow you to throw to certain pending elements
> saying  "start a new child". e.g., when you're in a UL and an LI and you
> see a new LI and realize  you need to tell the UL to start a new LI.
> I just use the object I'm filling as the throw tag.

This one I'm not sure I understand. Who does the throwing and who's
catching? And why did you need to unwind the call stack? (BTW, is the
"stack the elements" a data structure, or is it somehow tied to the
call stack?)

 -Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Kent M Pitman
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <sfwbrwnzx9k.fsf@shell01.TheWorld.com>
Peter Seibel <·····@javamonkey.com> writes:

> Kent M Pitman <······@world.std.com> writes:
> 
> > Peter Seibel <·····@javamonkey.com> writes:
> > 
> > > Given the flexibility of the condition system for managing
> > > coordination of code at different levels of the call stack, I'm having
> > > a hard time thinking of what I'd use CATCH/THROW for.
> > > 
> > > Does anyone have any favorite idioms they still use that feature
> > > CATCH/THROW?
> > 
> > The condition system is higher overhead due to its introduction of
> > introspection capabilities.
> 
> Just out of curiosity, isn't there some (unexposed) introspection
> going on with THROW too? That is, THROW has to be able to tell whether
> there's a CATCHer waiting for it before it actually unwinds the stack,
> right? So there must be some dynamic datastructure maintained under
> the covers to support that. Or are you talking about the space
> overhead of the extra information that has to be stored at runtime
> associated with restarts?

Yes and no.

If you implement your own CATCH/THROW (or consult mine), you'll
see there's easily the opportunity to implement a PENDING-CATCH-P
kind of thing.

(There was experimentation with this in Maclisp and it mostly was a 
disaster, as I recall.  We had all kinds of operators like CATCH-ALL,
CATCH-BARRIER, and whatnot that tried to allow users to be overly 
clever about this kind of thing.  Maybe a simple ability to test for
a pending catch wouldn't have been so bad, but these other things gave
you the power to invade others' abstractions and to thwart them, and
was generally overpowerful.  I think most of this was rightly left behind.)

However, the kind of introspection that restarts offer includes stuff
that would not be inferrable in general--that is, the additional adornment
of restarts with:
 - human language description of the effect
 - human prompting information for missing arguments
 
> > I think CATCH/THROW is used only rarely, but usually in situations
> > where many people these days would use a set of mutually recursive
> > functions using LABELS and a lexical RETURN[-FROM] to exit from a
> > tree-like search. Some people prefer to break this out into separate
> > top-level functions that do (a) not share a common lexical contour
> > so don't qualify for RETURN-FROM and (b) don't want to pass a
> > continuation arg that would be able to piggy-back the RETURN-FROM
> > operation.
> 
> That makes sense.
> 
> > > And if you do use CATCH/THROW, do you ever take advantage of the tag
> > > arguments to CATCH and THROW being evaluated? I.e. how often is the
> > > tag in either the CATCH or the THROW not a just quoted symbol?
> > 
> > I often use this in HTML parsing.  I build a stack of the elements that
> > are being filled and allow you to throw to certain pending elements
> > saying  "start a new child". e.g., when you're in a UL and an LI and you
> > see a new LI and realize  you need to tell the UL to start a new LI.
> > I just use the object I'm filling as the throw tag.
> 
> This one I'm not sure I understand. Who does the throwing and who's
> catching? And why did you need to unwind the call stack? (BTW, is the
> "stack the elements" a data structure, or is it somehow tied to the
> call stack?)

I prefer to tie it to the call stack, though presumably one doesn't have to.
A lot of parsers work like state machines, and keep all of their state
in data structures.  I like using the call stack.

It happens often that one gets to 

   <ul><li><p>foo<li>
                 ^
here and one wants to "throw" out of the pending LI to the UL and ask it
to spawn a new LI, but one doesn't want to lose the stuff one has been
parsing.  So rather than return the object parsed, I pre-cons each element
before beginning to parse it, and then operate by side-effect filling it.
That way, if a throw occurs out of one element, it's already linked into
the tree and the stuff-parsed-so-far is not lost.

However, there are two kinds of throws that can occur.  The simple case is

 <ul><li><p>foo</p><p>bar</ul>

which simply has to throw to the <ul> saying "i'm all done, you can return".
But in the case of 

 <ul><li><p>foo</p><p>bar<li>

you have to throw out of the <li> _AND ALSO_ tell it that a new <li> has
started.  Approximately [i.e., I have "tested" code elsewhere, but don't 
want to paste that code, so am sketching the general shape of it from memory]:

 (defun parse-into-element (element stream)
   (let ((contents '()) (new))
     (unwind-protect 
         (loop     
           (setq new
             (catch element
               (let ((*pending-elements* (cons element *pending-elements*)))
                 (return
                   (loop (let ((item (prog1 (or new (parse-any stream))
                                            (setq new nil)))
                               (temp))
                           (cond ((setq temp (closes-pending-element item))
                                  ;; <ul><li>...foo..</ul>
                                  (throw temp nil))
                                 ((start-tag-p item)
                                  ;; <foo>
                                  (cond ((setq temp (restarts-pending-element
                                                      item))
                                         ;; <ul><li>...foo..<li>
                                         ;; Must return to proper context
                                         ;; for attachment.
                                         (throw temp item))
                                        (t
                                         (push item contents)
                                         (unless (empty-tag-p item)
                                           (parse-into-element item stream)))))
                                 (t ;text, entity, etc.
                                  ;; foo or &foo;
                                  (push item contents)))))))))
           ;; Returning NIL means we're done
           ;; Returning a start tag means 
           (unless new (return)))
       (setf (element-contents) (nreverse contents)))))
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m3llvqexh1.fsf@javamonkey.com>
Kent M Pitman <······@world.std.com> writes:

> Peter Seibel <·····@javamonkey.com> writes:

> > This one I'm not sure I understand. Who does the throwing and
> > who's catching? And why did you need to unwind the call stack?
> > (BTW, is the "stack the elements" a data structure, or is it
> > somehow tied to the call stack?)
> 
> I prefer to tie it to the call stack, though presumably one doesn't
> have to. A lot of parsers work like state machines, and keep all of
> their state in data structures. I like using the call stack.
> 
> It happens often that one gets to 
> 
>    <ul><li><p>foo<li>
>                  ^
> here and one wants to "throw" out of the pending LI to the UL and ask it
> to spawn a new LI, but one doesn't want to lose the stuff one has been
> parsing.  So rather than return the object parsed, I pre-cons each element
> before beginning to parse it, and then operate by side-effect filling it.
> That way, if a throw occurs out of one element, it's already linked into
> the tree and the stuff-parsed-so-far is not lost.
> 
> However, there are two kinds of throws that can occur.  The simple case is
> 
>  <ul><li><p>foo</p><p>bar</ul>
> 
> which simply has to throw to the <ul> saying "i'm all done, you can return".
> But in the case of 
> 
>  <ul><li><p>foo</p><p>bar<li>
> 
> you have to throw out of the <li> _AND ALSO_ tell it that a new <li>
> has started. Approximately [i.e., I have "tested" code elsewhere,
> but don't want to paste that code, so am sketching the general shape
> of it from memory]:

Cool. Thanks.

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Rob Warnock
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <n7udneWczOpddGejXTWc-g@speakeasy.net>
Peter Seibel  <·····@javamonkey.com> wrote:
+---------------
| Given the flexibility of the condition system for managing
| coordination of code at different levels of the call stack, I'm having
| a hard time thinking of what I'd use CATCH/THROW for.
| 
| Does anyone have any favorite idioms they still use that feature
| CATCH/THROW?
+---------------

I ran into a situation just last week where CATCH/THROW was what came
first to mind as a solution, though thinking back on it I suppose I
could have used conditions just as easily...

Under Unix a given process can be in only one state at a time w.r.t. the
handling of a given Unix signal, but in implementations such as CMUCL
(on x86) which provide "green threads"[1], you often want different
threads to handle signals differently, at least in their control-flow
responses. In particular, I wanted a SIGPIPE (which is what you get if
your web server code is writing to a socket and a user hits the <STOP>
button on the client browser) to be handled by the thread that was writing
to the closed socket, *not* the MP::*INITIAL-PROCESS*. My perhaps-ugly
solution was as follows:

In the global initialization code:

	(defun sigpipe-handler (signal code scp)
	  (declare (ignore signal code scp))
	  (throw 'sigpipe 'sigpipe))

	;; Remember initial state & enable local handler.
	(defvar *initial-sigpipe-handler*
		(system:enable-interrupt :sigpipe #'sigpipe-handler))

In the per-thread server code [where the worker routine SERVE-REQUEST-1
will in the normal case do a (progn (finish-output stream) (close stream))
before returning]:

	(defun serve-request (func request)
	  (let ((stream (http-request-stream request)))
	    (when (eq 'sigpipe (catch 'sigpipe
				 (serve-request-1 func request stream)))
	      (log-msg "serve-request[~d]: SIGPIPE on fd ~d: ~a"
		       *request-sequence-number*
		       (unix::fd-stream-fd stream)
		       (http-request-self request))	; sanitized URI
	      ;; Avoid fd leakage.
	      (ignore-errors (close stream :abort t)))))   ; [2]

Note: SIGPIPE always occurs during a "write()" system call [or "close()",
which is why the above code keeps the CATCH active around the (close stream)
in SERVE-REQUEST-1] and thus is thread-synchronous, and thus the THROW
in the handler will be in the same thread context as the CATCH wrapped
around the offending "write()". [Caution: The same will *not* necessarily
be true for other Unix signals.]

If someone has something significantly cleaner to suggest, feel free
to do so. As noted at the beginning, I suppose I could have defined a
specific condition and used HANDLER-CASE/ERROR to get the same effect.
But in such a confined context CATCH/THROW seemed more "lightweight"
somehow. [Hmmm... Maybe my former C hacking with setjmp/longjmp bleeding
through...?]


-Rob

[1] That is, within-Unix-process multiprogramming -- what CMUCL *should*
    have called it, not "multiprocessing". (Which it isn't -- at least,
    not yet. Though SBCL...?)

[2] By experimentation(!) I discovered that in CMUCL a
    (close stream :abort t) will not do any additional "write()"s, and
    thus will not cause additional SIGPIPEs to occur. [A previous version
    of the handler that just did (ignore-errors (close stream)) had caused
    infinite recursion of SIGPIPEs, since each handler entry would try to
    CLOSE and eash CLOSE would try to flush the stream, which would cause
    a "write()" and... Oops.]

-----
Rob Warnock, PP-ASEL-IA		<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Kent M Pitman
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <sfw3chwok28.fsf@shell01.TheWorld.com>
····@rpw3.org (Rob Warnock) writes:

> Peter Seibel  <·····@javamonkey.com> wrote:
> +---------------
> | Given the flexibility of the condition system for managing
> | coordination of code at different levels of the call stack, I'm having
> | a hard time thinking of what I'd use CATCH/THROW for.
> | 
> | Does anyone have any favorite idioms they still use that feature
> | CATCH/THROW?
> +---------------
> 
> I ran into a situation just last week where CATCH/THROW was what came
> first to mind as a solution, though thinking back on it I suppose I
> could have used conditions just as easily...

Well, I don't have access to Xanalys sources, but a bit of poking about
in the Lisp Listener suggests they use CATCH/THROW to implement 
BLOCK/RETURN in some way. :)

  (funcall 
   (funcall
    (compile
     (defun foo ()
      (block nil
       #'(lambda ()
           (return 3)))))))

  Error: Uncaught throw of 3 to (NIL).

Speculating from this purely at the level of user-visible effects and
obvious implementations, which I hope it's legal to do without violating 
some reverse engineering promise I've made in my licensing agreements,
it looks like they're using (LIST NIL) as a low-tech version of gensym
[the size of (LIST NIL) is probably smaller than the size of a real
gensym, and less memory to clean up later].  These tags are probably 
established as throw tags during the dynamic extent and that disappear
upon unwind so that the RETURN will not try to jump to a non-existent or
recycled point in the stack as it might if they just used a raw stack
pointer.  

That's actually a pretty interesting and non-trivial use of catch/throw
if you ask me.  It's ironic that it's used to implement a facility that
appears superficially to preclude the need for catch/throw. I suppose 
if I thought harder about this it would be one of those yin/yang things
where if you have one it's enough to implement the other and you just have
to decide which one will be primitive.
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m3of0ka825.fsf@javamonkey.com>
Kent M Pitman <······@world.std.com> writes:

> That's actually a pretty interesting and non-trivial use of
> catch/throw if you ask me. It's ironic that it's used to implement a
> facility that appears superficially to preclude the need for
> catch/throw. I suppose if I thought harder about this it would be
> one of those yin/yang things where if you have one it's enough to
> implement the other and you just have to decide which one will be
> primitive.

So I was thinking about that same idea--that either BLOCK/RETURN-FROM
or CATCH/THROW might be implementable in terms of the other pair. I
figured out how to implement C/T with B/R-F (and a dynamic variable)
but couldn't think of a way to implement B/R-F on top of C/T without
writing a code walker to find the relevant RETURN-FROM forms.

My idea--which seems about the same as what you're infering Lispworks
is doing--was that a BLOCK would turn into a CATCH of a gensym (or
other unique objects such as (LIST NIL)) and then RETURN-FROM would
turn into a THROW of that same object. But that requires finding all
the RETURN-FROMs in the body of the BLOCK and transforming them at
macroexpand time, doesn't it?

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Kent M Pitman
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <sfwy8zo7dul.fsf@shell01.TheWorld.com>
Peter Seibel <·····@javamonkey.com> writes:

> Kent M Pitman <······@world.std.com> writes:
> 
> > That's actually a pretty interesting and non-trivial use of
> > catch/throw if you ask me. It's ironic that it's used to implement a
> > facility that appears superficially to preclude the need for
> > catch/throw. I suppose if I thought harder about this it would be
> > one of those yin/yang things where if you have one it's enough to
> > implement the other and you just have to decide which one will be
> > primitive.
> 
> So I was thinking about that same idea--that either BLOCK/RETURN-FROM
> or CATCH/THROW might be implementable in terms of the other pair. I
> figured out how to implement C/T with B/R-F (and a dynamic variable)
> but couldn't think of a way to implement B/R-F on top of C/T without
> writing a code walker to find the relevant RETURN-FROM forms.

Oh, it's not that hard and requires no code-walking.  This is one of the
chief good uses of FLET, incidentally.  I'm not going to spoil the fun
by just telling you, but I will say the solution is only 12 lines long,
including the 2-line helper function you need for nice error reporting.

You might want to google around for the answer.  I think the programming
technique you want came up in a discussion before with Drew McDermott
about whether FLET was at all useful (i.e., couldn't LABELS do everything),
and I was insisting that it's highly useful for implementing lexical 
constructs. :)  I'll wait a while before remarking further.
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m3el1g9srn.fsf@javamonkey.com>
Kent M Pitman <······@world.std.com> writes:

> Peter Seibel <·····@javamonkey.com> writes:
> 
> > Kent M Pitman <······@world.std.com> writes:
> > 
> > > That's actually a pretty interesting and non-trivial use of
> > > catch/throw if you ask me. It's ironic that it's used to implement a
> > > facility that appears superficially to preclude the need for
> > > catch/throw. I suppose if I thought harder about this it would be
> > > one of those yin/yang things where if you have one it's enough to
> > > implement the other and you just have to decide which one will be
> > > primitive.
> > 
> > So I was thinking about that same idea--that either BLOCK/RETURN-FROM
> > or CATCH/THROW might be implementable in terms of the other pair. I
> > figured out how to implement C/T with B/R-F (and a dynamic variable)
> > but couldn't think of a way to implement B/R-F on top of C/T without
> > writing a code walker to find the relevant RETURN-FROM forms.
> 
> Oh, it's not that hard and requires no code-walking.  This is one of the
> chief good uses of FLET, incidentally.  I'm not going to spoil the fun
> by just telling you, but I will say the solution is only 12 lines long,
> including the 2-line helper function you need for nice error reporting.

Duh. Of course. I was so focused on raw code transformation I forgot
about being able to create new bindings. Though I didn't end up using
FLET. (I also wimped out on the nice error reporting.) Here's my take.
(I'm assuming I can count on folks not to muck about with an
"implementation internal" package. If I really cared, I suppose I
could use something other than packages to intern my symbols in.)

Any flaws in this approach?

  (defpackage #:block-names (:use))

  (defun block-name (sym)
    (intern (symbol-name sym)  (find-package '#:block-names)))

  (defmacro blok (name &body body)
    (let ((tag (gensym)))
      `(catch ',tag
        (let ((,(block-name name) ',tag))
          ,@body))))

  (defmacro ret-from (name value-form)
    `(throw ,(block-name name) ,value-form))

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Kent M Pitman
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <sfwadc4gony.fsf@shell01.TheWorld.com>
Peter Seibel <·····@javamonkey.com> writes:

> ... I was so focused on raw code transformation I forgot about being
> able to create new bindings. Though I didn't end up using FLET.

Heh.  Maybe you should have.  Read on.  I'm not claiming you have to use
FLET -- it's just a nice use of FLET.

> (I also wimped out on the nice error reporting.) Here's my take.
> (I'm assuming I can count on folks not to muck about with an
> "implementation internal" package. If I really cared, I suppose I
> could use something other than packages to intern my symbols in.)

That's not the per-se problem.

> Any flaws in this approach?
> 
>   (defpackage #:block-names (:use))
> 
>   (defun block-name (sym)
>     (intern (symbol-name sym)  (find-package '#:block-names)))
> 
>   (defmacro blok (name &body body)
>     (let ((tag (gensym)))
>       `(catch ',tag
>         (let ((,(block-name name) ',tag))
>           ,@body))))
> 
>   (defmacro ret-from (name value-form)
>     `(throw ,(block-name name) ,value-form))

Yeah, this isn't quite right because blocks are not supposed to be
"reentrant".  Your implementation doesn't get confused in simple
lexical situations, but it does get confused across multiple calls.
(The reason you know this is because you're consing the gensym 
per-lexical-contour instead of per-call, which is "efficient" but
not "correct".) 

(Another clue that you were doing something wrong was that you were
not needing to use (block-name name) to find the tag to set up.
That means it wasn't going to vary per-catch, which means it wasn't
going to vary per-throw, which means you were going to lose.)

Now the only problem is to construct a situation 
that perturbs that case.  It looks like this will do it:

(defun foo (x)
  (blok zap
    (list 'foo
      (blok zing
        (if x 
            (funcall x)
            (ret-from zap #'(lambda () (ret-from zing 4))))))))

(foo nil) => #<interpreted closure (LAMBDA NIL (RET-FROM ZING 4))>

(foo (foo nil)) => (FOO 4)

I think you can fix your implementation by doing:

   (defmacro blok (name &body body)
     (let ((tagvar (block-name name)))
       `(let ((,tagvar (cons ',name '(block return point))))
           (declare (ignorable ,tagvar))
           (catch ,tagvar
             ,@body))))

Note that I eliminated the use of the gensymed tag since it's not useful
anyway and since the call to CONS gives you better error reporting.
I also added an ignorable declaration because it's annoying if you don't
put a ret-from in there to get an error.  Certain macros set up blocks
speculatively that don't get used.  DEFUN, for example.

(foo nil)
=> #<interpreted closure (LAMBDA NIL (RET-FROM ZING 4))>

(foo (foo nil))
Error: Uncaught throw of 4 to (ZING BLOCK RETURN POINT).
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m3adc49jz9.fsf@javamonkey.com>
Kent M Pitman <······@world.std.com> writes:

> Peter Seibel <·····@javamonkey.com> writes:
> 
> > ... I was so focused on raw code transformation I forgot about being
> > able to create new bindings. Though I didn't end up using FLET.
> 
> Heh. Maybe you should have. Read on. I'm not claiming you have to
> use FLET -- it's just a nice use of FLET.
> 
> > (I also wimped out on the nice error reporting.) Here's my take.
> > (I'm assuming I can count on folks not to muck about with an
> > "implementation internal" package. If I really cared, I suppose I
> > could use something other than packages to intern my symbols in.)
> 
> That's not the per-se problem.
> 
> > Any flaws in this approach?
> > 
> >   (defpackage #:block-names (:use))
> > 
> >   (defun block-name (sym)
> >     (intern (symbol-name sym)  (find-package '#:block-names)))
> > 
> >   (defmacro blok (name &body body)
> >     (let ((tag (gensym)))
> >       `(catch ',tag
> >         (let ((,(block-name name) ',tag))
> >           ,@body))))
> > 
> >   (defmacro ret-from (name value-form)
> >     `(throw ,(block-name name) ,value-form))
> 
> Yeah, this isn't quite right because blocks are not supposed to be
> "reentrant".  Your implementation doesn't get confused in simple
> lexical situations, but it does get confused across multiple calls.
> (The reason you know this is because you're consing the gensym 
> per-lexical-contour instead of per-call, which is "efficient" but
> not "correct".) 

Oh, yeah. Forgot about that. (Which is sort of ironic because the
reason I've been thinking about this stuff lately is because I've been
thinking about the condition system where, of course, closures over
RETURN-FROMs are quite important.)

> (Another clue that you were doing something wrong was that you were
> not needing to use (block-name name) to find the tag to set up. That
> means it wasn't going to vary per-catch, which means it wasn't going
> to vary per-throw, which means you were going to lose.)
> 
> Now the only problem is to construct a situation that perturbs that
> case. It looks like this will do it:
> 
> (defun foo (x)
>   (blok zap
>     (list 'foo
>       (blok zing
>         (if x 
>             (funcall x)
>             (ret-from zap #'(lambda () (ret-from zing 4))))))))
> 
> (foo nil) => #<interpreted closure (LAMBDA NIL (RET-FROM ZING 4))>
> 
> (foo (foo nil)) => (FOO 4)

Having only read your message up to here, this is what I came up with:

  (defmacro blok (name &body body)
    `(let ((,(block-name name) (list nil)))
      (catch ,(block-name name) ,@body)))

Anyway, that seems to do the right thing with FOO above.

> I think you can fix your implementation by doing:
> 
>    (defmacro blok (name &body body)
>      (let ((tagvar (block-name name)))
>        `(let ((,tagvar (cons ',name '(block return point))))
>            (declare (ignorable ,tagvar))
>            (catch ,tagvar
>              ,@body))))

Looks about the same, modulo the declare ignorable (good point) and
the more user-friendly catch tag in your version.

> (foo nil)
> => #<interpreted closure (LAMBDA NIL (RET-FROM ZING 4))>
> 
> (foo (foo nil))
> Error: Uncaught throw of 4 to (ZING BLOCK RETURN POINT).
> 

Interestingly, in ACL, if I rewrite FOO to use the real BLOCK and
RETURN-FROM, the error I get is.

  Error: Attempt to throw to the non-existent tag -268443947
    [condition type: CONTROL-ERROR]

as compared to the error from the blok/ret-from version:

  Error: Attempt to throw to the non-existent tag (NIL)
    [condition type: CONTROL-ERROR]

So I guess I could make some inferences about how Allegro implement
BLOCK and RETURN-FROM.

Now I guess I have to take the original hint and go figure out how to
write a version based on FLET. Thanks.

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m365ms9jtd.fsf@javamonkey.com>
Peter Seibel <·····@javamonkey.com> writes:

> So I guess I could make some inferences about how Allegro implement
> BLOCK and RETURN-FROM.

Let me take that back--I don't want to make any undue inferences,
especially in light of a very helpful email I just got from Steve
Haflich talking about various implementation strategies for
RETURN-FROM and THROW that suggests my inference is totally wrong.

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Steven M. Haflich
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <3EFC34BF.2040202@alum.mit.edu>
Peter Seibel wrote:
> Peter Seibel <·····@javamonkey.com> writes:

> 
>>So I guess I could make some inferences about how Allegro implement
>>BLOCK and RETURN-FROM.
> 
> Let me take that back--I don't want to make any undue inferences,
> especially in light of a very helpful email I just got from Steve
> Haflich talking about various implementation strategies for
> RETURN-FROM and THROW that suggests my inference is totally wrong.

I intended that response to go to the list as well, but I was
beta testing the latest Mozilla, and it was having problems.
Below is that post.  It approaches the return-from / throw issue
frmo the perspective of the semantics the two need to implement in
interaction with various special forms.

=======

Peter Seibel wrote:

 > But that was really my point in this question. I was thinking of cases
 > where it was part of the API--as in "this function will return thus on
 > such a value except in the following situation when it will THROW this
 > other value to such and such a tag." If some other thing happens to
 > use THROW under the covers then that's none of my business.

Your reasoning is impeccable as a language lawyer but hardly worthy of
serious consideration by an implementor.  Perhaps you should apply for
the next opening on the Supreme Court... :-)

According to the ANS there is no relation between return-from and throw.
However, in implementation terms it is very easy to hierarchicalize these
operators.

return-from is only cognizant of lexical constructs.  throw is cognizant
of dynamic constructs.  In some sense, this makes throw a more powerful
operation, but this ituition is not warranted by anything in the ANS.
So we need to consider that return-from and throw have to do in
interaction with other operators.

Implementationally (according to plausible implementation, but not ir any
sense mandated) a return-from that does not cross any lambda countours nor
any special variable binding contours nor any unwind-protect forms could
be implemented by a simple branch instruction.  But if a return-from
crosses any special bindings, it must arrange to unwind those bindings.
If it crosses any unwind-protect forms, it must arrange to invoke those
cleanup forms.  (It also has to disestablish condition handlers and
restarts, but since these systems are obviously implemented by special
bindings, which have the same dynamic binding characteristics, dealing
with specials automatically does what is necessary.)

A throw must always unwind any special bindings, and much invoke any
intervening unwind-protect clanups.  In some cases the compiler may be
able to deduce that there can be no such intervening forms, and might
rewrite a throw as a simple goto-implemented return-from, in general
throw is used in circumstances precisely where such rewriting is not
generally possible.  (Otherwise the programmer could and should have
used return-from.  You see, return-from is easier to understand when
_reading_ code because its target _must_ be lexically visible, whereas
the current catch target of a throw _might_ be lexically visible but
might also be somewhere in the surrounding dynamic context but not in
the lexical context.  And of course, catch tags are computed and might
not be manifest constants.)

In other words, throw is usually a nontrivial runtime operation, whereas
return-from can sometimes be coded as a underlying-machine goto.  When it
is not possible to implement a return-from this way bcause it crosses a
special binding or a lambda function contour, compilers will generally
rewrite the return-from as a throw, because throw automatically implements
the exact semantics necessary in this circumstance.

Therefore in an implementational sense, return-from is usually considered a
simpler lower-power-in-generated-code operation than a throw.  Of course,
this reasoning may be obviated entirely in presence of a block compiler
that can reason about semantic interaction across separate top-level
function definitions...
From: Kalle Olavi Niemitalo
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <87he6c5a2s.fsf@Astalo.kon.iki.fi>
Peter Seibel <·····@javamonkey.com> writes:

>   (defpackage #:block-names (:use))
>
>   (defun block-name (sym)
>     (intern (symbol-name sym)  (find-package '#:block-names)))

Checking the symbol-name is not enough:

  (defpackage #:first (:use))
  (defpackage #:second (:use))
  (blok first::tag
    (blok second::tag
      (ret-from first::tag 'right))
    'wrong)

Uninterned symbols would be even worse.
From: Kent M Pitman
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <sfwbrwkc9s9.fsf@shell01.TheWorld.com>
Kalle Olavi Niemitalo <···@iki.fi> writes:

> Peter Seibel <·····@javamonkey.com> writes:
> 
> >   (defpackage #:block-names (:use))
> >
> >   (defun block-name (sym)
> >     (intern (symbol-name sym)  (find-package '#:block-names)))
> 
> Checking the symbol-name is not enough:
> 
>   (defpackage #:first (:use))
>   (defpackage #:second (:use))
>   (blok first::tag
>     (blok second::tag
>       (ret-from first::tag 'right))
>     'wrong)
> 
> Uninterned symbols would be even worse.

Heh.  Good catch.  I barely looked at that part of his solution,
but had assumed he was doing more like

 (defvar *my-package* *package*)

 (defun block-name (sym)
   (let ((*package* *my-package*)) ;(mostly) force package name to print
     (intern (prin1-to-string sym) *package*)))

Even so, your comment about gensyms is interesting.  (I wonder if
LispWorks, which uses this trick for SETF names, fails on the
construction of SETF's for lookalike gensyms.  Hmmm.... Something
to try later.)

In any case, as far as catch/throw goes, the FLET trick I alluded to,
(if he figures it out) will avoid this problem. :)
From: Kalle Olavi Niemitalo
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <877k77qxgx.fsf@Astalo.kon.iki.fi>
Kent M Pitman <······@world.std.com> writes:

> In any case, as far as catch/throw goes, the FLET trick I alluded to,
> (if he figures it out) will avoid this problem. :)

I came up with this...

  (defun escape (name results)
    (error 'control-error))

  (defmacro ret-from (name &optional result)
    `(escape ',name (multiple-value-list ,result)))

  (defmacro blok (name &body body)
    (check-type name symbol)
    (let ((tag (gensym "TAG")))
      `(let ((,tag (list nil)))
         (catch ,tag
           (flet ((escape (name results)
                    (if (eq name ',name)
                        (throw ,tag (values-list results))
                        (escape name results))))
             ,@body)))))

Having the local ESCAPE functions compare the name of the block
one by one seemed initially wrong to me, as it makes the cost of
the control transfer depend linearly on the number of blocks
thus escaped.  But perhaps the cost of stack unwinding is linear
already.

Also, this version does not detect orphan RET-FROM forms at
compile time.  I suppose that would need MACROLET, MACROEXPAND-1
and &ENVIRONMENT.  Or do you have a trick for that too?
From: Kalle Olavi Niemitalo
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <87r85fpd22.fsf@Astalo.kon.iki.fi>
Kalle Olavi Niemitalo <···@iki.fi> writes:

> Also, this version does not detect orphan RET-FROM forms at
> compile time.

Here is one that does.

  (define-symbol-macro .block-alist. ())

  (defmacro ret-from (name &optional result &environment environment)
    (check-type name symbol)
    (let* ((block-alist (macroexpand-1 '.block-alist. environment))
           (mapping (assoc name block-alist :test #'eq)))
      (if mapping
          `(throw ,(cdr mapping) ,result)
          ;; FIXME: Should the error case first evaluate RESULT?
          '(error 'control-error))))

  (defmacro blok (name &body body &environment environment)
    (check-type name symbol)
    (let ((block-alist (macroexpand-1 '.block-alist. environment))
          (tag-variable (gensym (symbol-name name))))
      `(let ((,tag-variable (list nil)))
         (catch ,tag-variable
           (symbol-macrolet ((.block-alist. ((,name . ,tag-variable)
                                             ,@block-alist)))
             ,@body)))))
From: Kalle Olavi Niemitalo
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <87k7b7p5ia.fsf@Astalo.kon.iki.fi>
Kalle Olavi Niemitalo <···@iki.fi> writes:

> I came up with this...

Although I prefer the explicitly compile-time operation of the
second version, here is a refinement of the first one that need
not construct lists to hold multiple values.

  (defun block-tag (name)
    (error 'control-error))

  (defmacro ret-from (name &optional result)
    `(throw (block-tag ',name) ,result))

  (defmacro blok (name &body body)
    (check-type name symbol)
    (let ((tag (gensym "TAG")))
      `(let ((,tag (list nil)))
         (catch ,tag
           (flet ((block-tag (name)
                    (if (eq name ',name)
                        ,tag
                        (block-tag name))))
             ,@body)))))

The local variable used in the expansion of the macro could also
be called TAG directly, if that symbol is not otherwise used.
Doing that and removing the CHECK-TYPE form would bring the code
down to the advertised 12 lines, not counting blanks.

> Having the local ESCAPE functions compare the name of the block
> one by one seemed initially wrong to me, as it makes the cost of
> the control transfer depend linearly on the number of blocks
> thus escaped.

On second thought, the compiler is free to inline calls to the
local functions and collapse them to a mere access to the
appropriate variable.
From: Ivan Boldyrev
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <h5svsxhch.ln2@elaleph.borges.cgitftp.uiggm.nsc.ru>
On 8422 day of my life Kent M. Pitman wrote:

> Heh.  Good catch.

Lispnik proverb:  Good THROW -- good CATCH. :)

-- 
Ivan Boldyrev

                                                  Is 'morning' a gerund?
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m31xxg9c7m.fsf@javamonkey.com>
Kalle Olavi Niemitalo <···@iki.fi> writes:

> Peter Seibel <·····@javamonkey.com> writes:
> 
> >   (defpackage #:block-names (:use))
> >
> >   (defun block-name (sym)
> >     (intern (symbol-name sym)  (find-package '#:block-names)))
> 
> Checking the symbol-name is not enough:
> 
>   (defpackage #:first (:use))
>   (defpackage #:second (:use))
>   (blok first::tag
>     (blok second::tag
>       (ret-from first::tag 'right))
>     'wrong)
> 
> Uninterned symbols would be even worse.

Blech. Good point. I guess my original instinct that using a special
package was a bit of a kludge was right. Since what I *really* want is
a mapping from the symbols that appear in the code to otherwise unused
symbols, I should just express that directly, as in something like:

  (defvar *block-names* (make-hash-table :test #'eq))

  (defun block-name (sym)
    (destructuring-bind (name present)
        (gethash sym *block-names*)
      (unless present
        (setf name (gensym))
        (setf (gethash sym *block-names*) name))
      name))

That also avoids the problem of folks messing with my special package.

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Coby Beck
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <bdh91i$2b52$1@otis.netspace.net.au>
"Peter Seibel" <·····@javamonkey.com> wrote in message
···················@javamonkey.com...
> Kalle Olavi Niemitalo <···@iki.fi> writes:
> > Uninterned symbols would be even worse.
>
> Blech. Good point. I guess my original instinct that using a special
> package was a bit of a kludge was right. Since what I *really* want is
> a mapping from the symbols that appear in the code to otherwise unused
> symbols, I should just express that directly, as in something like:
>
>   (defvar *block-names* (make-hash-table :test #'eq))
>
>   (defun block-name (sym)
>     (destructuring-bind (name present)
>         (gethash sym *block-names*)
>       (unless present
>         (setf name (gensym))
>         (setf (gethash sym *block-names*) name))
>       name))

Sorry for kicking you will you're down... ;-)

but I think you need multiple-value-bind not destructuring-bind.

-- 
Coby Beck
(remove #\Space "coby 101 @ bigpond . com")
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m3wuf78gh7.fsf@javamonkey.com>
"Coby Beck" <·····@mercury.bc.ca> writes:

> "Peter Seibel" <·····@javamonkey.com> wrote in message
> ···················@javamonkey.com...
> > Kalle Olavi Niemitalo <···@iki.fi> writes:
> > > Uninterned symbols would be even worse.
> >
> > Blech. Good point. I guess my original instinct that using a special
> > package was a bit of a kludge was right. Since what I *really* want is
> > a mapping from the symbols that appear in the code to otherwise unused
> > symbols, I should just express that directly, as in something like:
> >
> >   (defvar *block-names* (make-hash-table :test #'eq))
> >
> >   (defun block-name (sym)
> >     (destructuring-bind (name present)
> >         (gethash sym *block-names*)
> >       (unless present
> >         (setf name (gensym))
> >         (setf (gethash sym *block-names*) name))
> >       name))
> 
> Sorry for kicking you will you're down... ;-)
> 
> but I think you need multiple-value-bind not destructuring-bind.

Ow. Of course. I'd better stop posting my code sketches for a while.
(At least until I figure out the FLET version.)

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m3smpv8dmf.fsf@javamonkey.com>
Peter Seibel <·····@javamonkey.com> writes:

> "Coby Beck" <·····@mercury.bc.ca> writes:
> 
> > "Peter Seibel" <·····@javamonkey.com> wrote in message
> > ···················@javamonkey.com...
> > > Kalle Olavi Niemitalo <···@iki.fi> writes:
> > > > Uninterned symbols would be even worse.
> > >
> > > Blech. Good point. I guess my original instinct that using a special
> > > package was a bit of a kludge was right. Since what I *really* want is
> > > a mapping from the symbols that appear in the code to otherwise unused
> > > symbols, I should just express that directly, as in something like:
> > >
> > >   (defvar *block-names* (make-hash-table :test #'eq))
> > >
> > >   (defun block-name (sym)
> > >     (destructuring-bind (name present)
> > >         (gethash sym *block-names*)
> > >       (unless present
> > >         (setf name (gensym))
> > >         (setf (gethash sym *block-names*) name))
> > >       name))
> > 
> > Sorry for kicking you will you're down... ;-)
> > 
> > but I think you need multiple-value-bind not destructuring-bind.
> 
> Ow. Of course. I'd better stop posting my code sketches for a while.
> (At least until I figure out the FLET version.)

Okay, here goes my crack at a FLET-based version. 

  (defmacro blok2 (name &body body)
    (let ((tagvar (gensym)))
      `(let ((,tagvar (cons ',name '(block exit))))
        (flet ((block-name (n)
                 (if (eq ',name n) ,tagvar (block-name n))))
          (catch (block-name ',name)
            ,@body)))))

  (defmacro ret-from2 (name value-form)
    `(throw (block-name ',name) ,value-form))

  (defun block-name (n)
    (error "Attempted to return from unknown block ~a~%" n))


Or, if I really wanted to enhance the hygine of the BLOK2 macro by
hiding the name of the FLET'd function I could do this:

  (eval-when (:compile-toplevel :load-toplevel :execute)
    (defvar *block-name-fn-name* (gensym))

    (setf (symbol-function *block-name-fn-name*)
          #'(lambda (n)
              (error "Attempted to return from unknown block ~a~%" n))))

  (defmacro blok2 (name &body body)
    (let ((tagvar (gensym)))
      `(let ((,tagvar (cons ',name '(block exit))))
        (flet ((,*block-name-fn-name* (n)
                 (if (eq ',name n) ,tagvar (,*block-name-fn-name* n))))
          (catch (,*block-name-fn-name* ',name)
            ,@body)))))

  (defmacro ret-from2 (name value-form)
    `(throw (,*block-name-fn-name* ',name) ,value-form))


Is that overkill?

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Kalle Olavi Niemitalo
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <87he6bp4s9.fsf@Astalo.kon.iki.fi>
Peter Seibel <·····@javamonkey.com> writes:

> Is that overkill?

It seems quite pointless; you wanted to prevent external access
to the function BLOCK-NAME, but now you instead have a variable
*BLOCK-NAME-FN-NAME* that can be accessed similarly.

Things you could do:

(a) Put the symbols in a custom package and don't export
    BLOCK-NAME.  One can still access it with the double-colon
    syntax, but it's not your fault if someone chooses to do
    that.

(b) Use #1=#:BLOCK-NAME and wrap the definitions in a PROGN so
    that they'll be read together.  I wonder how the file
    compiler would handle that.  And of course, anyone can still
    access that symbol via MACROEXPAND.

(c) Make BLOCK-NAME-FN-NAME a lexical variable.  The macro
    functions would then be closures.  The MACROEXPAND cheat
    works here too.
From: Peter Seibel
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <m3k7b7805o.fsf@javamonkey.com>
Kalle Olavi Niemitalo <···@iki.fi> writes:

> Peter Seibel <·····@javamonkey.com> writes:
> 
> > Is that overkill?
> 
> It seems quite pointless; you wanted to prevent external access
> to the function BLOCK-NAME, but now you instead have a variable
> *BLOCK-NAME-FN-NAME* that can be accessed similarly.

I don't think it's *quite* pointless. With the *BLOCK-NAME-FN-NAME*
version, there's no FLET that someone could write in the body of a
BLOK that would shadow the internal function--they'd have to write a
macro that specifically grabs the uninterned symbol out of
*BLOCK-NAME-FN-NAME* and uses it (the way BLOK does). So that's a
layer of protection not provided by simply using an unexported symbol
from a "private" package.

Of course, if that's sufficient in this case, then it should also be
sufficient for most variables in macros but folks seem to continue to
use gensym'd symbols for them. What's the difference?

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Kalle Olavi Niemitalo
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <87vfuqvdl9.fsf@Astalo.kon.iki.fi>
Peter Seibel <·····@javamonkey.com> writes:

> With the *BLOCK-NAME-FN-NAME* version, there's no FLET that
> someone could write in the body of a BLOK that would shadow the
> internal function--they'd have to write a macro that
> specifically grabs the uninterned symbol out of
> *BLOCK-NAME-FN-NAME* and uses it (the way BLOK does).

  (flet ((#.*block-name-fn-name* ()
            ...))
    ...)

That doesn't look much harder to use than a package prefix.

> Of course, if that's sufficient in this case, then it should also be
> sufficient for most variables in macros but folks seem to continue to
> use gensym'd symbols for them. What's the difference?

I think I'd use gensyms for bindings that are only meant to be
used from that expansion of the macro, but internal symbols for
bindings that must be coordinated with different expansions or
top-level definitions.

Having the expansion of a macro bind a gensym makes it easy to
verify that nothing else uses the binding, if that's the intent.
The variable in DEFMACRO that holds the gensym can also have a
nice short name without conflicting with anything else.

Having the expansion of a macro bind an internal symbol requires
reserving that use of the symbol in the whole package, to avoid
accidental variable (or function) capture.  This means the name
must be more carefully chosen.

There is a rule that says you mustn't FLET any symbols exported
from COMMON-LISP that are already defined as functions.  If you
adopt a similar rule for your own functions too, then the
top-level definition of BLOCK-NAME suffices to reserve that
symbol as a function name.  Of course, because the top-level
definition of BLOCK-NAME is *meant* to be hidden by the FLET in
BLOK2, that FLET must still be allowed.
From: Kalle Olavi Niemitalo
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <87of0ivcbp.fsf@Astalo.kon.iki.fi>
Kent M Pitman <······@world.std.com> writes:

> I think the programming technique you want came up in a
> discussion before with Drew McDermott about whether FLET was at
> all useful (i.e., couldn't LABELS do everything), and I was
> insisting that it's highly useful for implementing lexical
> constructs. :)

LABELS can do that too!

  (labels ((temp () (depth)))
    (labels ((depth () (1+ (temp))))
      ...))

It's more cumbersome than FLET, for sure.
From: Daniel Barlow
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <87fzlx3pp5.fsf@noetbook.telent.net>
····@rpw3.org (Rob Warnock) writes:

> responses. In particular, I wanted a SIGPIPE (which is what you get if
> your web server code is writing to a socket and a user hits the <STOP>
> button on the client browser) to be handled by the thread that was writing
> to the closed socket, *not* the MP::*INITIAL-PROCESS*. My perhaps-ugly

I found it easier to ignore SIGPIPE altogether.  You still get EPIPE
back from your write() or close() call (which is passed up to Lisp as 
some condition you can handle) so you're not losing any information.

The primary use for SIGPIPE seems to be in utilities which don't
check write() return values, e.g. to ensure that the cat in ``cat
bigfile | head'' doesn't spin endlessly.

> [1] That is, within-Unix-process multiprogramming -- what CMUCL *should*
>     have called it, not "multiprocessing". (Which it isn't -- at least,
>     not yet. Though SBCL...?)

Native (clone()-based) threads on Linux x86.  See

  http://www.xach.com/sbcl/doc/extensions.html#AEN655 

  http://sbcl-internals.cliki.net/Threading

and there's also a "traditional" clim-sys interface for SBCL in
McCLIM, which given sufficient tuits will eventually be bundled with 
SBCL itself


-dan

-- 

   http://www.cliki.net/ - Link farm for free CL-on-Unix resources 
From: Rob Warnock
Subject: Re: catch/throw useful for anything?
Date: 
Message-ID: <tUOdncb7692QE2CjXTWc-w@speakeasy.net>
Daniel Barlow  <···@telent.net> wrote:
+---------------
| ····@rpw3.org (Rob Warnock) writes:
| 
| > responses. In particular, I wanted a SIGPIPE (which is what you get if
| > your web server code is writing to a socket and a user hits the <STOP>
| > button on the client browser) to be handled by the thread that was writing
| > to the closed socket, *not* the MP::*INITIAL-PROCESS*. My perhaps-ugly
| 
| I found it easier to ignore SIGPIPE altogether.  You still get EPIPE
| back from your write() or close() call (which is passed up to Lisp as 
| some condition you can handle) so you're not losing any information.
+---------------

*Doh!* You're right, of course. That's a lot simpler.  Thanks!

There *is* one reason in my application to distinguish between an EPIPE
and other errors -- for the others I try to write a helpful message back
to the user's browser (as well as an internal log), but for an EPIPE that
won't work, of course. I just have to be careful not to fall into infinite
regress in that case...

+---------------
| The primary use for SIGPIPE seems to be in utilities which don't
| check write() return values, e.g. to ensure that the cat in ``cat
| bigfile | head'' doesn't spin endlessly.
+---------------

Yup. Exactly. But any decent Lisp will check all O/S calls...  ;-}


-Rob

-----
Rob Warnock, PP-ASEL-IA		<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607